{-# LANGUAGE PartialTypeSignatures #-}
{-# OPTIONS_GHC -Wno-partial-type-signatures #-}

-- 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.Internal
  ( internalAPI,
    InternalAPI,
    deleteLoop,
    safeForever,
  )
where

import Control.Exception.Safe (catchAny)
import Control.Lens hiding (Getter, Setter, (.=))
import Data.ByteString.UTF8 qualified as UTF8
import Data.Id as Id
import Data.Json.Util (ToJSONObject (toJSONObject))
import Data.Map qualified as Map
import Data.Qualified
import Data.Range
import Data.Singletons
import Data.Time
import Galley.API.Action
import Galley.API.Clients qualified as Clients
import Galley.API.Create qualified as Create
import Galley.API.Error
import Galley.API.LegalHold (unsetTeamLegalholdWhitelistedH)
import Galley.API.LegalHold.Conflicts
import Galley.API.MLS.Removal
import Galley.API.One2One
import Galley.API.Public.Servant
import Galley.API.Query qualified as Query
import Galley.API.Teams
import Galley.API.Teams qualified as Teams
import Galley.API.Teams.Features
import Galley.API.Teams.Features.Get
import Galley.API.Update qualified as Update
import Galley.API.Util
import Galley.App
import Galley.Data.Conversation qualified as Data
import Galley.Effects
import Galley.Effects.BackendNotificationQueueAccess
import Galley.Effects.ClientStore
import Galley.Effects.ConversationStore
import Galley.Effects.CustomBackendStore
import Galley.Effects.LegalHoldStore as LegalHoldStore
import Galley.Effects.MemberStore qualified as E
import Galley.Effects.ServiceStore
import Galley.Effects.TeamStore
import Galley.Effects.TeamStore qualified as E
import Galley.Monad
import Galley.Options hiding (brig)
import Galley.Queue qualified as Q
import Galley.Types.Conversations.Members (RemoteMember (rmId))
import Galley.Types.UserList
import Gundeck.Types.Push.V2 qualified as PushV2
import Imports hiding (head)
import Network.AMQP qualified as Q
import Polysemy
import Polysemy.Error
import Polysemy.Input
import Polysemy.TinyLog qualified as P
import Servant
import System.Logger.Class hiding (Path, name)
import System.Logger.Class qualified as Log
import Wire.API.Conversation hiding (Member)
import Wire.API.Conversation.Action
import Wire.API.Error
import Wire.API.Error.Galley
import Wire.API.Event.Conversation
import Wire.API.Event.LeaveReason
import Wire.API.Federation.API
import Wire.API.Federation.API.Galley
import Wire.API.Federation.Error
import Wire.API.Routes.API
import Wire.API.Routes.Internal.Brig.EJPD
import Wire.API.Routes.Internal.Galley
import Wire.API.Routes.Internal.Galley.TeamsIntra
import Wire.API.Routes.MultiTablePaging (mtpHasMore, mtpPagingState, mtpResults)
import Wire.API.Routes.MultiTablePaging qualified as MTP
import Wire.API.Team.Feature
import Wire.API.User.Client
import Wire.NotificationSubsystem
import Wire.Sem.Paging
import Wire.Sem.Paging.Cassandra

internalAPI :: API InternalAPI GalleyEffects
internalAPI :: API InternalAPI GalleyEffects
internalAPI =
  forall {k1} {k2} (api1 :: k1) (api2 :: k2) (r1 :: EffectRow)
       (r2 :: EffectRow).
(ServerT api1 (Sem r1) -> ServerT api2 (Sem r2))
-> API api1 r1 -> API api2 r2
forall api1 api2 (r1 :: EffectRow) (r2 :: EffectRow).
(ServerT api1 (Sem r1) -> ServerT api2 (Sem r2))
-> API api1 r1 -> API api2 r2
hoistAPI @InternalAPIBase (Named
   "status"
   (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]
      ())
 :<|> (Named
         "delete-user"
         (Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
          -> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
          -> QualifiedWithTag 'QLocal UserId
          -> Maybe ConnId
          -> 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]
               ())
       :<|> (Named
               "connect"
               (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
                -> Connect
                -> 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]
                     (ResponseForExistedCreated Conversation))
             :<|> (Named
                     "get-conversation-clients"
                     (GroupId
                      -> 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]
                           ClientList)
                   :<|> (Named
                           "guard-legalhold-policy-conflicts"
                           (GuardLegalholdPolicyConflicts
                            -> 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]
                                 ())
                         :<|> ((TeamId
                                -> Named
                                     "set-team-legalhold-whitelisted"
                                     (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]
                                        ())
                                   :<|> (Named
                                           "unset-team-legalhold-whitelisted"
                                           (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]
                                              ())
                                         :<|> Named
                                                "get-team-legalhold-whitelisted"
                                                (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]
                                                   Bool)))
                               :<|> ((TeamId
                                      -> Named
                                           "get-team-internal"
                                           (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]
                                              TeamData)
                                         :<|> (Named
                                                 "create-binding-team"
                                                 (UserId
                                                  -> BindingNewTeam
                                                  -> 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]
                                                       TeamId)
                                               :<|> (Named
                                                       "delete-binding-team"
                                                       (Bool
                                                        -> 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]
                                                             ())
                                                     :<|> (Named
                                                             "get-team-name"
                                                             (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]
                                                                TeamName)
                                                           :<|> (Named
                                                                   "update-team-status"
                                                                   (TeamStatusUpdate
                                                                    -> 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]
                                                                         ())
                                                                 :<|> ((Named
                                                                          "unchecked-add-team-member"
                                                                          (NewTeamMember
                                                                           -> 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]
                                                                                ())
                                                                        :<|> (Named
                                                                                "unchecked-get-team-members"
                                                                                (Maybe
                                                                                   (Range
                                                                                      1
                                                                                      HardTruncationLimit
                                                                                      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]
                                                                                      TeamMemberList)
                                                                              :<|> (Named
                                                                                      "unchecked-get-team-member"
                                                                                      (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]
                                                                                            TeamMember)
                                                                                    :<|> (Named
                                                                                            "can-user-join-team"
                                                                                            (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]
                                                                                               ())
                                                                                          :<|> Named
                                                                                                 "unchecked-update-team-member"
                                                                                                 (NewTeamMember
                                                                                                  -> 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]
                                                                                                       ())))))
                                                                       :<|> (Named
                                                                               "user-is-team-owner"
                                                                               (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]
                                                                                     ())
                                                                             :<|> (Named
                                                                                     "get-search-visibility-internal"
                                                                                     (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]
                                                                                        TeamSearchVisibilityView)
                                                                                   :<|> Named
                                                                                          "set-search-visibility-internal"
                                                                                          (TeamSearchVisibilityView
                                                                                           -> 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]
                                                                                                ())))))))))
                                     :<|> ((Named
                                              "get-team-members"
                                              (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]
                                                    TeamMemberList)
                                            :<|> (Named
                                                    "get-team-id"
                                                    (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]
                                                          TeamId)
                                                  :<|> (Named
                                                          "test-get-clients"
                                                          (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]
                                                                [ClientId])
                                                        :<|> (Named
                                                                "test-add-client"
                                                                (UserId
                                                                 -> ClientId
                                                                 -> 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]
                                                                      ())
                                                              :<|> (Named
                                                                      "test-delete-client"
                                                                      (UserId
                                                                       -> ClientId
                                                                       -> 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]
                                                                            ())
                                                                    :<|> (Named
                                                                            "add-service"
                                                                            (Service
                                                                             -> 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]
                                                                                  ())
                                                                          :<|> (Named
                                                                                  "delete-service"
                                                                                  (ServiceRef
                                                                                   -> 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]
                                                                                        ())
                                                                                :<|> (Named
                                                                                        "i-add-bot"
                                                                                        (QualifiedWithTag
                                                                                           'QLocal
                                                                                           UserId
                                                                                         -> ConnId
                                                                                         -> AddBot
                                                                                         -> 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]
                                                                                              Event)
                                                                                      :<|> (Named
                                                                                              "delete-bot"
                                                                                              (QualifiedWithTag
                                                                                                 'QLocal
                                                                                                 UserId
                                                                                               -> Maybe
                                                                                                    ConnId
                                                                                               -> RemoveBot
                                                                                               -> 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]
                                                                                                    (UpdateResult
                                                                                                       Event))
                                                                                            :<|> (Named
                                                                                                    "put-custom-backend"
                                                                                                    (Domain
                                                                                                     -> CustomBackend
                                                                                                     -> 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]
                                                                                                          ())
                                                                                                  :<|> Named
                                                                                                         "delete-custom-backend"
                                                                                                         (Domain
                                                                                                          -> 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]
                                                                                                               ())))))))))))
                                           :<|> (Named
                                                   "upsert-one2one"
                                                   (UpsertOne2OneConversationRequest
                                                    -> 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]
                                                         ())
                                                 :<|> ((((Named
                                                            '("iget", LegalholdConfig)
                                                            (TeamId
                                                             -> 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]
                                                                  (LockableFeature LegalholdConfig))
                                                          :<|> (Named
                                                                  '("iput", LegalholdConfig)
                                                                  (TeamId
                                                                   -> Feature LegalholdConfig
                                                                   -> 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]
                                                                        (LockableFeature
                                                                           LegalholdConfig))
                                                                :<|> Named
                                                                       '("ipatch", LegalholdConfig)
                                                                       (TeamId
                                                                        -> LockableFeaturePatch
                                                                             LegalholdConfig
                                                                        -> 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]
                                                                             (LockableFeature
                                                                                LegalholdConfig))))
                                                         :<|> ((Named
                                                                  '("iget", SSOConfig)
                                                                  (TeamId
                                                                   -> 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]
                                                                        (LockableFeature SSOConfig))
                                                                :<|> (Named
                                                                        '("iput", SSOConfig)
                                                                        (TeamId
                                                                         -> Feature SSOConfig
                                                                         -> 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]
                                                                              (LockableFeature
                                                                                 SSOConfig))
                                                                      :<|> Named
                                                                             '("ipatch", SSOConfig)
                                                                             (TeamId
                                                                              -> LockableFeaturePatch
                                                                                   SSOConfig
                                                                              -> 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]
                                                                                   (LockableFeature
                                                                                      SSOConfig))))
                                                               :<|> ((Named
                                                                        '("iget",
                                                                          SearchVisibilityAvailableConfig)
                                                                        (TeamId
                                                                         -> 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]
                                                                              (LockableFeature
                                                                                 SearchVisibilityAvailableConfig))
                                                                      :<|> (Named
                                                                              '("iput",
                                                                                SearchVisibilityAvailableConfig)
                                                                              (TeamId
                                                                               -> Feature
                                                                                    SearchVisibilityAvailableConfig
                                                                               -> 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]
                                                                                    (LockableFeature
                                                                                       SearchVisibilityAvailableConfig))
                                                                            :<|> Named
                                                                                   '("ipatch",
                                                                                     SearchVisibilityAvailableConfig)
                                                                                   (TeamId
                                                                                    -> LockableFeaturePatch
                                                                                         SearchVisibilityAvailableConfig
                                                                                    -> 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]
                                                                                         (LockableFeature
                                                                                            SearchVisibilityAvailableConfig))))
                                                                     :<|> ((Named
                                                                              '("iget",
                                                                                SearchVisibilityInboundConfig)
                                                                              (TeamId
                                                                               -> 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]
                                                                                    (LockableFeature
                                                                                       SearchVisibilityInboundConfig))
                                                                            :<|> (Named
                                                                                    '("iput",
                                                                                      SearchVisibilityInboundConfig)
                                                                                    (TeamId
                                                                                     -> Feature
                                                                                          SearchVisibilityInboundConfig
                                                                                     -> 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]
                                                                                          (LockableFeature
                                                                                             SearchVisibilityInboundConfig))
                                                                                  :<|> Named
                                                                                         '("ipatch",
                                                                                           SearchVisibilityInboundConfig)
                                                                                         (TeamId
                                                                                          -> LockableFeaturePatch
                                                                                               SearchVisibilityInboundConfig
                                                                                          -> 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]
                                                                                               (LockableFeature
                                                                                                  SearchVisibilityInboundConfig))))
                                                                           :<|> ((Named
                                                                                    '("iget",
                                                                                      ValidateSAMLEmailsConfig)
                                                                                    (TeamId
                                                                                     -> 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]
                                                                                          (LockableFeature
                                                                                             ValidateSAMLEmailsConfig))
                                                                                  :<|> (Named
                                                                                          '("iput",
                                                                                            ValidateSAMLEmailsConfig)
                                                                                          (TeamId
                                                                                           -> Feature
                                                                                                ValidateSAMLEmailsConfig
                                                                                           -> 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]
                                                                                                (LockableFeature
                                                                                                   ValidateSAMLEmailsConfig))
                                                                                        :<|> Named
                                                                                               '("ipatch",
                                                                                                 ValidateSAMLEmailsConfig)
                                                                                               (TeamId
                                                                                                -> LockableFeaturePatch
                                                                                                     ValidateSAMLEmailsConfig
                                                                                                -> 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]
                                                                                                     (LockableFeature
                                                                                                        ValidateSAMLEmailsConfig))))
                                                                                 :<|> ((Named
                                                                                          '("iget",
                                                                                            DigitalSignaturesConfig)
                                                                                          (TeamId
                                                                                           -> 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]
                                                                                                (LockableFeature
                                                                                                   DigitalSignaturesConfig))
                                                                                        :<|> (Named
                                                                                                '("iput",
                                                                                                  DigitalSignaturesConfig)
                                                                                                (TeamId
                                                                                                 -> Feature
                                                                                                      DigitalSignaturesConfig
                                                                                                 -> 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]
                                                                                                      (LockableFeature
                                                                                                         DigitalSignaturesConfig))
                                                                                              :<|> Named
                                                                                                     '("ipatch",
                                                                                                       DigitalSignaturesConfig)
                                                                                                     (TeamId
                                                                                                      -> LockableFeaturePatch
                                                                                                           DigitalSignaturesConfig
                                                                                                      -> 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]
                                                                                                           (LockableFeature
                                                                                                              DigitalSignaturesConfig))))
                                                                                       :<|> ((Named
                                                                                                '("iget",
                                                                                                  AppLockConfig)
                                                                                                (TeamId
                                                                                                 -> 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]
                                                                                                      (LockableFeature
                                                                                                         AppLockConfig))
                                                                                              :<|> (Named
                                                                                                      '("iput",
                                                                                                        AppLockConfig)
                                                                                                      (TeamId
                                                                                                       -> Feature
                                                                                                            AppLockConfig
                                                                                                       -> 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]
                                                                                                            (LockableFeature
                                                                                                               AppLockConfig))
                                                                                                    :<|> Named
                                                                                                           '("ipatch",
                                                                                                             AppLockConfig)
                                                                                                           (TeamId
                                                                                                            -> LockableFeaturePatch
                                                                                                                 AppLockConfig
                                                                                                            -> 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]
                                                                                                                 (LockableFeature
                                                                                                                    AppLockConfig))))
                                                                                             :<|> ((Named
                                                                                                      '("iget",
                                                                                                        FileSharingConfig)
                                                                                                      (TeamId
                                                                                                       -> 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]
                                                                                                            (LockableFeature
                                                                                                               FileSharingConfig))
                                                                                                    :<|> (Named
                                                                                                            '("iput",
                                                                                                              FileSharingConfig)
                                                                                                            (TeamId
                                                                                                             -> Feature
                                                                                                                  FileSharingConfig
                                                                                                             -> 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]
                                                                                                                  (LockableFeature
                                                                                                                     FileSharingConfig))
                                                                                                          :<|> Named
                                                                                                                 '("ipatch",
                                                                                                                   FileSharingConfig)
                                                                                                                 (TeamId
                                                                                                                  -> LockableFeaturePatch
                                                                                                                       FileSharingConfig
                                                                                                                  -> 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]
                                                                                                                       (LockableFeature
                                                                                                                          FileSharingConfig))))
                                                                                                   :<|> (Named
                                                                                                           '("iget",
                                                                                                             ClassifiedDomainsConfig)
                                                                                                           (TeamId
                                                                                                            -> 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]
                                                                                                                 (LockableFeature
                                                                                                                    ClassifiedDomainsConfig))
                                                                                                         :<|> ((Named
                                                                                                                  '("iget",
                                                                                                                    ConferenceCallingConfig)
                                                                                                                  (TeamId
                                                                                                                   -> 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]
                                                                                                                        (LockableFeature
                                                                                                                           ConferenceCallingConfig))
                                                                                                                :<|> (Named
                                                                                                                        '("iput",
                                                                                                                          ConferenceCallingConfig)
                                                                                                                        (TeamId
                                                                                                                         -> Feature
                                                                                                                              ConferenceCallingConfig
                                                                                                                         -> 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]
                                                                                                                              (LockableFeature
                                                                                                                                 ConferenceCallingConfig))
                                                                                                                      :<|> Named
                                                                                                                             '("ipatch",
                                                                                                                               ConferenceCallingConfig)
                                                                                                                             (TeamId
                                                                                                                              -> LockableFeaturePatch
                                                                                                                                   ConferenceCallingConfig
                                                                                                                              -> 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]
                                                                                                                                   (LockableFeature
                                                                                                                                      ConferenceCallingConfig))))
                                                                                                               :<|> ((Named
                                                                                                                        '("iget",
                                                                                                                          SelfDeletingMessagesConfig)
                                                                                                                        (TeamId
                                                                                                                         -> 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]
                                                                                                                              (LockableFeature
                                                                                                                                 SelfDeletingMessagesConfig))
                                                                                                                      :<|> (Named
                                                                                                                              '("iput",
                                                                                                                                SelfDeletingMessagesConfig)
                                                                                                                              (TeamId
                                                                                                                               -> Feature
                                                                                                                                    SelfDeletingMessagesConfig
                                                                                                                               -> 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]
                                                                                                                                    (LockableFeature
                                                                                                                                       SelfDeletingMessagesConfig))
                                                                                                                            :<|> Named
                                                                                                                                   '("ipatch",
                                                                                                                                     SelfDeletingMessagesConfig)
                                                                                                                                   (TeamId
                                                                                                                                    -> LockableFeaturePatch
                                                                                                                                         SelfDeletingMessagesConfig
                                                                                                                                    -> 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]
                                                                                                                                         (LockableFeature
                                                                                                                                            SelfDeletingMessagesConfig))))
                                                                                                                     :<|> ((Named
                                                                                                                              '("iget",
                                                                                                                                GuestLinksConfig)
                                                                                                                              (TeamId
                                                                                                                               -> 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]
                                                                                                                                    (LockableFeature
                                                                                                                                       GuestLinksConfig))
                                                                                                                            :<|> (Named
                                                                                                                                    '("iput",
                                                                                                                                      GuestLinksConfig)
                                                                                                                                    (TeamId
                                                                                                                                     -> Feature
                                                                                                                                          GuestLinksConfig
                                                                                                                                     -> 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]
                                                                                                                                          (LockableFeature
                                                                                                                                             GuestLinksConfig))
                                                                                                                                  :<|> Named
                                                                                                                                         '("ipatch",
                                                                                                                                           GuestLinksConfig)
                                                                                                                                         (TeamId
                                                                                                                                          -> LockableFeaturePatch
                                                                                                                                               GuestLinksConfig
                                                                                                                                          -> 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]
                                                                                                                                               (LockableFeature
                                                                                                                                                  GuestLinksConfig))))
                                                                                                                           :<|> ((Named
                                                                                                                                    '("iget",
                                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                                    (TeamId
                                                                                                                                     -> 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]
                                                                                                                                          (LockableFeature
                                                                                                                                             SndFactorPasswordChallengeConfig))
                                                                                                                                  :<|> (Named
                                                                                                                                          '("iput",
                                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                                          (TeamId
                                                                                                                                           -> Feature
                                                                                                                                                SndFactorPasswordChallengeConfig
                                                                                                                                           -> 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]
                                                                                                                                                (LockableFeature
                                                                                                                                                   SndFactorPasswordChallengeConfig))
                                                                                                                                        :<|> Named
                                                                                                                                               '("ipatch",
                                                                                                                                                 SndFactorPasswordChallengeConfig)
                                                                                                                                               (TeamId
                                                                                                                                                -> LockableFeaturePatch
                                                                                                                                                     SndFactorPasswordChallengeConfig
                                                                                                                                                -> 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]
                                                                                                                                                     (LockableFeature
                                                                                                                                                        SndFactorPasswordChallengeConfig))))
                                                                                                                                 :<|> ((Named
                                                                                                                                          '("iget",
                                                                                                                                            MLSConfig)
                                                                                                                                          (TeamId
                                                                                                                                           -> 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]
                                                                                                                                                (LockableFeature
                                                                                                                                                   MLSConfig))
                                                                                                                                        :<|> (Named
                                                                                                                                                '("iput",
                                                                                                                                                  MLSConfig)
                                                                                                                                                (TeamId
                                                                                                                                                 -> Feature
                                                                                                                                                      MLSConfig
                                                                                                                                                 -> 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]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         MLSConfig))
                                                                                                                                              :<|> Named
                                                                                                                                                     '("ipatch",
                                                                                                                                                       MLSConfig)
                                                                                                                                                     (TeamId
                                                                                                                                                      -> LockableFeaturePatch
                                                                                                                                                           MLSConfig
                                                                                                                                                      -> 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]
                                                                                                                                                           (LockableFeature
                                                                                                                                                              MLSConfig))))
                                                                                                                                       :<|> ((Named
                                                                                                                                                '("iget",
                                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                (TeamId
                                                                                                                                                 -> 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]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         ExposeInvitationURLsToTeamAdminConfig))
                                                                                                                                              :<|> (Named
                                                                                                                                                      '("iput",
                                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                      (TeamId
                                                                                                                                                       -> Feature
                                                                                                                                                            ExposeInvitationURLsToTeamAdminConfig
                                                                                                                                                       -> 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]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               ExposeInvitationURLsToTeamAdminConfig))
                                                                                                                                                    :<|> Named
                                                                                                                                                           '("ipatch",
                                                                                                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                           (TeamId
                                                                                                                                                            -> LockableFeaturePatch
                                                                                                                                                                 ExposeInvitationURLsToTeamAdminConfig
                                                                                                                                                            -> 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]
                                                                                                                                                                 (LockableFeature
                                                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig))))
                                                                                                                                             :<|> ((Named
                                                                                                                                                      '("iget",
                                                                                                                                                        OutlookCalIntegrationConfig)
                                                                                                                                                      (TeamId
                                                                                                                                                       -> 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]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               OutlookCalIntegrationConfig))
                                                                                                                                                    :<|> (Named
                                                                                                                                                            '("iput",
                                                                                                                                                              OutlookCalIntegrationConfig)
                                                                                                                                                            (TeamId
                                                                                                                                                             -> Feature
                                                                                                                                                                  OutlookCalIntegrationConfig
                                                                                                                                                             -> 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]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     OutlookCalIntegrationConfig))
                                                                                                                                                          :<|> Named
                                                                                                                                                                 '("ipatch",
                                                                                                                                                                   OutlookCalIntegrationConfig)
                                                                                                                                                                 (TeamId
                                                                                                                                                                  -> LockableFeaturePatch
                                                                                                                                                                       OutlookCalIntegrationConfig
                                                                                                                                                                  -> 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]
                                                                                                                                                                       (LockableFeature
                                                                                                                                                                          OutlookCalIntegrationConfig))))
                                                                                                                                                   :<|> ((Named
                                                                                                                                                            '("iget",
                                                                                                                                                              MlsE2EIdConfig)
                                                                                                                                                            (TeamId
                                                                                                                                                             -> 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]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     MlsE2EIdConfig))
                                                                                                                                                          :<|> (Named
                                                                                                                                                                  '("iput",
                                                                                                                                                                    MlsE2EIdConfig)
                                                                                                                                                                  (TeamId
                                                                                                                                                                   -> Feature
                                                                                                                                                                        MlsE2EIdConfig
                                                                                                                                                                   -> 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]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           MlsE2EIdConfig))
                                                                                                                                                                :<|> Named
                                                                                                                                                                       '("ipatch",
                                                                                                                                                                         MlsE2EIdConfig)
                                                                                                                                                                       (TeamId
                                                                                                                                                                        -> LockableFeaturePatch
                                                                                                                                                                             MlsE2EIdConfig
                                                                                                                                                                        -> 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]
                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                MlsE2EIdConfig))))
                                                                                                                                                         :<|> ((Named
                                                                                                                                                                  '("iget",
                                                                                                                                                                    MlsMigrationConfig)
                                                                                                                                                                  (TeamId
                                                                                                                                                                   -> 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]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           MlsMigrationConfig))
                                                                                                                                                                :<|> (Named
                                                                                                                                                                        '("iput",
                                                                                                                                                                          MlsMigrationConfig)
                                                                                                                                                                        (TeamId
                                                                                                                                                                         -> Feature
                                                                                                                                                                              MlsMigrationConfig
                                                                                                                                                                         -> 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]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 MlsMigrationConfig))
                                                                                                                                                                      :<|> Named
                                                                                                                                                                             '("ipatch",
                                                                                                                                                                               MlsMigrationConfig)
                                                                                                                                                                             (TeamId
                                                                                                                                                                              -> LockableFeaturePatch
                                                                                                                                                                                   MlsMigrationConfig
                                                                                                                                                                              -> 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]
                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                      MlsMigrationConfig))))
                                                                                                                                                               :<|> ((Named
                                                                                                                                                                        '("iget",
                                                                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                                                                        (TeamId
                                                                                                                                                                         -> 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]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 EnforceFileDownloadLocationConfig))
                                                                                                                                                                      :<|> (Named
                                                                                                                                                                              '("iput",
                                                                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                                                                              (TeamId
                                                                                                                                                                               -> Feature
                                                                                                                                                                                    EnforceFileDownloadLocationConfig
                                                                                                                                                                               -> 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]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       EnforceFileDownloadLocationConfig))
                                                                                                                                                                            :<|> Named
                                                                                                                                                                                   '("ipatch",
                                                                                                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                                                                                                   (TeamId
                                                                                                                                                                                    -> LockableFeaturePatch
                                                                                                                                                                                         EnforceFileDownloadLocationConfig
                                                                                                                                                                                    -> 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]
                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                            EnforceFileDownloadLocationConfig))))
                                                                                                                                                                     :<|> (Named
                                                                                                                                                                             '("iget",
                                                                                                                                                                               LimitedEventFanoutConfig)
                                                                                                                                                                             (TeamId
                                                                                                                                                                              -> 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]
                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                      LimitedEventFanoutConfig))
                                                                                                                                                                           :<|> (Named
                                                                                                                                                                                   '("iput",
                                                                                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                                                                                   (TeamId
                                                                                                                                                                                    -> Feature
                                                                                                                                                                                         LimitedEventFanoutConfig
                                                                                                                                                                                    -> 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]
                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                            LimitedEventFanoutConfig))
                                                                                                                                                                                 :<|> Named
                                                                                                                                                                                        '("ipatch",
                                                                                                                                                                                          LimitedEventFanoutConfig)
                                                                                                                                                                                        (TeamId
                                                                                                                                                                                         -> LockableFeaturePatch
                                                                                                                                                                                              LimitedEventFanoutConfig
                                                                                                                                                                                         -> 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]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 LimitedEventFanoutConfig)))))))))))))))))))))))
                                                        :<|> (Named
                                                                '("ilock", FileSharingConfig)
                                                                (TeamId
                                                                 -> LockStatus
                                                                 -> 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]
                                                                      LockStatusResponse)
                                                              :<|> (Named
                                                                      '("ilock",
                                                                        ConferenceCallingConfig)
                                                                      (TeamId
                                                                       -> LockStatus
                                                                       -> 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]
                                                                            LockStatusResponse)
                                                                    :<|> (Named
                                                                            '("ilock",
                                                                              SelfDeletingMessagesConfig)
                                                                            (TeamId
                                                                             -> LockStatus
                                                                             -> 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]
                                                                                  LockStatusResponse)
                                                                          :<|> (Named
                                                                                  '("ilock",
                                                                                    GuestLinksConfig)
                                                                                  (TeamId
                                                                                   -> LockStatus
                                                                                   -> 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]
                                                                                        LockStatusResponse)
                                                                                :<|> (Named
                                                                                        '("ilock",
                                                                                          SndFactorPasswordChallengeConfig)
                                                                                        (TeamId
                                                                                         -> LockStatus
                                                                                         -> 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]
                                                                                              LockStatusResponse)
                                                                                      :<|> (Named
                                                                                              '("ilock",
                                                                                                MLSConfig)
                                                                                              (TeamId
                                                                                               -> LockStatus
                                                                                               -> 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]
                                                                                                    LockStatusResponse)
                                                                                            :<|> (Named
                                                                                                    '("ilock",
                                                                                                      OutlookCalIntegrationConfig)
                                                                                                    (TeamId
                                                                                                     -> LockStatus
                                                                                                     -> 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]
                                                                                                          LockStatusResponse)
                                                                                                  :<|> (Named
                                                                                                          '("ilock",
                                                                                                            MlsE2EIdConfig)
                                                                                                          (TeamId
                                                                                                           -> LockStatus
                                                                                                           -> 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]
                                                                                                                LockStatusResponse)
                                                                                                        :<|> (Named
                                                                                                                '("ilock",
                                                                                                                  MlsMigrationConfig)
                                                                                                                (TeamId
                                                                                                                 -> LockStatus
                                                                                                                 -> 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]
                                                                                                                      LockStatusResponse)
                                                                                                              :<|> (Named
                                                                                                                      '("ilock",
                                                                                                                        EnforceFileDownloadLocationConfig)
                                                                                                                      (TeamId
                                                                                                                       -> LockStatus
                                                                                                                       -> 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]
                                                                                                                            LockStatusResponse)
                                                                                                                    :<|> (Named
                                                                                                                            '("igetmulti",
                                                                                                                              SearchVisibilityInboundConfig)
                                                                                                                            (TeamFeatureNoConfigMultiRequest
                                                                                                                             -> 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]
                                                                                                                                  (TeamFeatureNoConfigMultiResponse
                                                                                                                                     SearchVisibilityInboundConfig))
                                                                                                                          :<|> Named
                                                                                                                                 "feature-configs-internal"
                                                                                                                                 (Maybe
                                                                                                                                    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]
                                                                                                                                       AllTeamFeatures)))))))))))))
                                                       :<|> (Named
                                                               "get-federation-status"
                                                               (QualifiedWithTag 'QLocal UserId
                                                                -> RemoteDomains
                                                                -> 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]
                                                                     FederationStatus)
                                                             :<|> ((Named
                                                                      "conversation-get-member"
                                                                      (ConvId
                                                                       -> 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]
                                                                            (Maybe Member))
                                                                    :<|> (Named
                                                                            "conversation-accept-v2"
                                                                            (QualifiedWithTag
                                                                               'QLocal UserId
                                                                             -> Maybe ConnId
                                                                             -> 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]
                                                                                  Conversation)
                                                                          :<|> (Named
                                                                                  "conversation-block-unqualified"
                                                                                  (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]
                                                                                        ())
                                                                                :<|> (Named
                                                                                        "conversation-block"
                                                                                        (QualifiedWithTag
                                                                                           'QLocal
                                                                                           UserId
                                                                                         -> Qualified
                                                                                              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]
                                                                                              ())
                                                                                      :<|> (Named
                                                                                              "conversation-unblock-unqualified"
                                                                                              (QualifiedWithTag
                                                                                                 'QLocal
                                                                                                 UserId
                                                                                               -> Maybe
                                                                                                    ConnId
                                                                                               -> 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]
                                                                                                    Conversation)
                                                                                            :<|> (Named
                                                                                                    "conversation-unblock"
                                                                                                    (QualifiedWithTag
                                                                                                       'QLocal
                                                                                                       UserId
                                                                                                     -> Maybe
                                                                                                          ConnId
                                                                                                     -> Qualified
                                                                                                          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]
                                                                                                          ())
                                                                                                  :<|> (Named
                                                                                                          "conversation-meta"
                                                                                                          (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]
                                                                                                                ConversationMetadata)
                                                                                                        :<|> (Named
                                                                                                                "conversation-mls-one-to-one"
                                                                                                                (QualifiedWithTag
                                                                                                                   'QLocal
                                                                                                                   UserId
                                                                                                                 -> Qualified
                                                                                                                      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]
                                                                                                                      Conversation)
                                                                                                              :<|> Named
                                                                                                                     "conversation-mls-one-to-one-established"
                                                                                                                     (QualifiedWithTag
                                                                                                                        'QLocal
                                                                                                                        UserId
                                                                                                                      -> Qualified
                                                                                                                           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]
                                                                                                                           Bool)))))))))
                                                                   :<|> Named
                                                                          "get-conversations-by-user"
                                                                          (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]
                                                                                [EJPDConvInfo])))))))))))))
-> Named
     "status"
     (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]
        ())
   :<|> (Named
           "delete-user"
           (Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
            -> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
            -> QualifiedWithTag 'QLocal UserId
            -> Maybe ConnId
            -> 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]
                 ())
         :<|> (Named
                 "connect"
                 (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
                  -> Connect
                  -> 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]
                       (ResponseForExistedCreated Conversation))
               :<|> (Named
                       "get-conversation-clients"
                       (GroupId
                        -> 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]
                             ClientList)
                     :<|> (Named
                             "guard-legalhold-policy-conflicts"
                             (GuardLegalholdPolicyConflicts
                              -> 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]
                                   ())
                           :<|> ((TeamId
                                  -> Named
                                       "set-team-legalhold-whitelisted"
                                       (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]
                                          ())
                                     :<|> (Named
                                             "unset-team-legalhold-whitelisted"
                                             (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]
                                                ())
                                           :<|> Named
                                                  "get-team-legalhold-whitelisted"
                                                  (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]
                                                     Bool)))
                                 :<|> ((TeamId
                                        -> Named
                                             "get-team-internal"
                                             (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]
                                                TeamData)
                                           :<|> (Named
                                                   "create-binding-team"
                                                   (UserId
                                                    -> BindingNewTeam
                                                    -> 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]
                                                         TeamId)
                                                 :<|> (Named
                                                         "delete-binding-team"
                                                         (Bool
                                                          -> 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]
                                                               ())
                                                       :<|> (Named
                                                               "get-team-name"
                                                               (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]
                                                                  TeamName)
                                                             :<|> (Named
                                                                     "update-team-status"
                                                                     (TeamStatusUpdate
                                                                      -> 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]
                                                                           ())
                                                                   :<|> ((Named
                                                                            "unchecked-add-team-member"
                                                                            (NewTeamMember
                                                                             -> 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]
                                                                                  ())
                                                                          :<|> (Named
                                                                                  "unchecked-get-team-members"
                                                                                  (Maybe
                                                                                     (Range
                                                                                        1
                                                                                        HardTruncationLimit
                                                                                        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]
                                                                                        TeamMemberList)
                                                                                :<|> (Named
                                                                                        "unchecked-get-team-member"
                                                                                        (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]
                                                                                              TeamMember)
                                                                                      :<|> (Named
                                                                                              "can-user-join-team"
                                                                                              (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]
                                                                                                 ())
                                                                                            :<|> Named
                                                                                                   "unchecked-update-team-member"
                                                                                                   (NewTeamMember
                                                                                                    -> 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]
                                                                                                         ())))))
                                                                         :<|> (Named
                                                                                 "user-is-team-owner"
                                                                                 (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]
                                                                                       ())
                                                                               :<|> (Named
                                                                                       "get-search-visibility-internal"
                                                                                       (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]
                                                                                          TeamSearchVisibilityView)
                                                                                     :<|> Named
                                                                                            "set-search-visibility-internal"
                                                                                            (TeamSearchVisibilityView
                                                                                             -> 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]
                                                                                                  ())))))))))
                                       :<|> ((Named
                                                "get-team-members"
                                                (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]
                                                      TeamMemberList)
                                              :<|> (Named
                                                      "get-team-id"
                                                      (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]
                                                            TeamId)
                                                    :<|> (Named
                                                            "test-get-clients"
                                                            (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]
                                                                  [ClientId])
                                                          :<|> (Named
                                                                  "test-add-client"
                                                                  (UserId
                                                                   -> ClientId
                                                                   -> 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]
                                                                        ())
                                                                :<|> (Named
                                                                        "test-delete-client"
                                                                        (UserId
                                                                         -> ClientId
                                                                         -> 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]
                                                                              ())
                                                                      :<|> (Named
                                                                              "add-service"
                                                                              (Service
                                                                               -> 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]
                                                                                    ())
                                                                            :<|> (Named
                                                                                    "delete-service"
                                                                                    (ServiceRef
                                                                                     -> 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]
                                                                                          ())
                                                                                  :<|> (Named
                                                                                          "i-add-bot"
                                                                                          (QualifiedWithTag
                                                                                             'QLocal
                                                                                             UserId
                                                                                           -> ConnId
                                                                                           -> AddBot
                                                                                           -> 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]
                                                                                                Event)
                                                                                        :<|> (Named
                                                                                                "delete-bot"
                                                                                                (QualifiedWithTag
                                                                                                   'QLocal
                                                                                                   UserId
                                                                                                 -> Maybe
                                                                                                      ConnId
                                                                                                 -> RemoveBot
                                                                                                 -> 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]
                                                                                                      (UpdateResult
                                                                                                         Event))
                                                                                              :<|> (Named
                                                                                                      "put-custom-backend"
                                                                                                      (Domain
                                                                                                       -> CustomBackend
                                                                                                       -> 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]
                                                                                                            ())
                                                                                                    :<|> Named
                                                                                                           "delete-custom-backend"
                                                                                                           (Domain
                                                                                                            -> 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]
                                                                                                                 ())))))))))))
                                             :<|> (Named
                                                     "upsert-one2one"
                                                     (UpsertOne2OneConversationRequest
                                                      -> 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]
                                                           ())
                                                   :<|> ((((Named
                                                              '("iget", LegalholdConfig)
                                                              (TeamId
                                                               -> 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]
                                                                    (LockableFeature
                                                                       LegalholdConfig))
                                                            :<|> (Named
                                                                    '("iput", LegalholdConfig)
                                                                    (TeamId
                                                                     -> Feature LegalholdConfig
                                                                     -> 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]
                                                                          (LockableFeature
                                                                             LegalholdConfig))
                                                                  :<|> Named
                                                                         '("ipatch",
                                                                           LegalholdConfig)
                                                                         (TeamId
                                                                          -> LockableFeaturePatch
                                                                               LegalholdConfig
                                                                          -> 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]
                                                                               (LockableFeature
                                                                                  LegalholdConfig))))
                                                           :<|> ((Named
                                                                    '("iget", SSOConfig)
                                                                    (TeamId
                                                                     -> 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]
                                                                          (LockableFeature
                                                                             SSOConfig))
                                                                  :<|> (Named
                                                                          '("iput", SSOConfig)
                                                                          (TeamId
                                                                           -> Feature SSOConfig
                                                                           -> 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]
                                                                                (LockableFeature
                                                                                   SSOConfig))
                                                                        :<|> Named
                                                                               '("ipatch",
                                                                                 SSOConfig)
                                                                               (TeamId
                                                                                -> LockableFeaturePatch
                                                                                     SSOConfig
                                                                                -> 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]
                                                                                     (LockableFeature
                                                                                        SSOConfig))))
                                                                 :<|> ((Named
                                                                          '("iget",
                                                                            SearchVisibilityAvailableConfig)
                                                                          (TeamId
                                                                           -> 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]
                                                                                (LockableFeature
                                                                                   SearchVisibilityAvailableConfig))
                                                                        :<|> (Named
                                                                                '("iput",
                                                                                  SearchVisibilityAvailableConfig)
                                                                                (TeamId
                                                                                 -> Feature
                                                                                      SearchVisibilityAvailableConfig
                                                                                 -> 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]
                                                                                      (LockableFeature
                                                                                         SearchVisibilityAvailableConfig))
                                                                              :<|> Named
                                                                                     '("ipatch",
                                                                                       SearchVisibilityAvailableConfig)
                                                                                     (TeamId
                                                                                      -> LockableFeaturePatch
                                                                                           SearchVisibilityAvailableConfig
                                                                                      -> 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]
                                                                                           (LockableFeature
                                                                                              SearchVisibilityAvailableConfig))))
                                                                       :<|> ((Named
                                                                                '("iget",
                                                                                  SearchVisibilityInboundConfig)
                                                                                (TeamId
                                                                                 -> 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]
                                                                                      (LockableFeature
                                                                                         SearchVisibilityInboundConfig))
                                                                              :<|> (Named
                                                                                      '("iput",
                                                                                        SearchVisibilityInboundConfig)
                                                                                      (TeamId
                                                                                       -> Feature
                                                                                            SearchVisibilityInboundConfig
                                                                                       -> 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]
                                                                                            (LockableFeature
                                                                                               SearchVisibilityInboundConfig))
                                                                                    :<|> Named
                                                                                           '("ipatch",
                                                                                             SearchVisibilityInboundConfig)
                                                                                           (TeamId
                                                                                            -> LockableFeaturePatch
                                                                                                 SearchVisibilityInboundConfig
                                                                                            -> 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]
                                                                                                 (LockableFeature
                                                                                                    SearchVisibilityInboundConfig))))
                                                                             :<|> ((Named
                                                                                      '("iget",
                                                                                        ValidateSAMLEmailsConfig)
                                                                                      (TeamId
                                                                                       -> 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]
                                                                                            (LockableFeature
                                                                                               ValidateSAMLEmailsConfig))
                                                                                    :<|> (Named
                                                                                            '("iput",
                                                                                              ValidateSAMLEmailsConfig)
                                                                                            (TeamId
                                                                                             -> Feature
                                                                                                  ValidateSAMLEmailsConfig
                                                                                             -> 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]
                                                                                                  (LockableFeature
                                                                                                     ValidateSAMLEmailsConfig))
                                                                                          :<|> Named
                                                                                                 '("ipatch",
                                                                                                   ValidateSAMLEmailsConfig)
                                                                                                 (TeamId
                                                                                                  -> LockableFeaturePatch
                                                                                                       ValidateSAMLEmailsConfig
                                                                                                  -> 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]
                                                                                                       (LockableFeature
                                                                                                          ValidateSAMLEmailsConfig))))
                                                                                   :<|> ((Named
                                                                                            '("iget",
                                                                                              DigitalSignaturesConfig)
                                                                                            (TeamId
                                                                                             -> 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]
                                                                                                  (LockableFeature
                                                                                                     DigitalSignaturesConfig))
                                                                                          :<|> (Named
                                                                                                  '("iput",
                                                                                                    DigitalSignaturesConfig)
                                                                                                  (TeamId
                                                                                                   -> Feature
                                                                                                        DigitalSignaturesConfig
                                                                                                   -> 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]
                                                                                                        (LockableFeature
                                                                                                           DigitalSignaturesConfig))
                                                                                                :<|> Named
                                                                                                       '("ipatch",
                                                                                                         DigitalSignaturesConfig)
                                                                                                       (TeamId
                                                                                                        -> LockableFeaturePatch
                                                                                                             DigitalSignaturesConfig
                                                                                                        -> 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]
                                                                                                             (LockableFeature
                                                                                                                DigitalSignaturesConfig))))
                                                                                         :<|> ((Named
                                                                                                  '("iget",
                                                                                                    AppLockConfig)
                                                                                                  (TeamId
                                                                                                   -> 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]
                                                                                                        (LockableFeature
                                                                                                           AppLockConfig))
                                                                                                :<|> (Named
                                                                                                        '("iput",
                                                                                                          AppLockConfig)
                                                                                                        (TeamId
                                                                                                         -> Feature
                                                                                                              AppLockConfig
                                                                                                         -> 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]
                                                                                                              (LockableFeature
                                                                                                                 AppLockConfig))
                                                                                                      :<|> Named
                                                                                                             '("ipatch",
                                                                                                               AppLockConfig)
                                                                                                             (TeamId
                                                                                                              -> LockableFeaturePatch
                                                                                                                   AppLockConfig
                                                                                                              -> 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]
                                                                                                                   (LockableFeature
                                                                                                                      AppLockConfig))))
                                                                                               :<|> ((Named
                                                                                                        '("iget",
                                                                                                          FileSharingConfig)
                                                                                                        (TeamId
                                                                                                         -> 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]
                                                                                                              (LockableFeature
                                                                                                                 FileSharingConfig))
                                                                                                      :<|> (Named
                                                                                                              '("iput",
                                                                                                                FileSharingConfig)
                                                                                                              (TeamId
                                                                                                               -> Feature
                                                                                                                    FileSharingConfig
                                                                                                               -> 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]
                                                                                                                    (LockableFeature
                                                                                                                       FileSharingConfig))
                                                                                                            :<|> Named
                                                                                                                   '("ipatch",
                                                                                                                     FileSharingConfig)
                                                                                                                   (TeamId
                                                                                                                    -> LockableFeaturePatch
                                                                                                                         FileSharingConfig
                                                                                                                    -> 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]
                                                                                                                         (LockableFeature
                                                                                                                            FileSharingConfig))))
                                                                                                     :<|> (Named
                                                                                                             '("iget",
                                                                                                               ClassifiedDomainsConfig)
                                                                                                             (TeamId
                                                                                                              -> 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]
                                                                                                                   (LockableFeature
                                                                                                                      ClassifiedDomainsConfig))
                                                                                                           :<|> ((Named
                                                                                                                    '("iget",
                                                                                                                      ConferenceCallingConfig)
                                                                                                                    (TeamId
                                                                                                                     -> 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]
                                                                                                                          (LockableFeature
                                                                                                                             ConferenceCallingConfig))
                                                                                                                  :<|> (Named
                                                                                                                          '("iput",
                                                                                                                            ConferenceCallingConfig)
                                                                                                                          (TeamId
                                                                                                                           -> Feature
                                                                                                                                ConferenceCallingConfig
                                                                                                                           -> 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]
                                                                                                                                (LockableFeature
                                                                                                                                   ConferenceCallingConfig))
                                                                                                                        :<|> Named
                                                                                                                               '("ipatch",
                                                                                                                                 ConferenceCallingConfig)
                                                                                                                               (TeamId
                                                                                                                                -> LockableFeaturePatch
                                                                                                                                     ConferenceCallingConfig
                                                                                                                                -> 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]
                                                                                                                                     (LockableFeature
                                                                                                                                        ConferenceCallingConfig))))
                                                                                                                 :<|> ((Named
                                                                                                                          '("iget",
                                                                                                                            SelfDeletingMessagesConfig)
                                                                                                                          (TeamId
                                                                                                                           -> 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]
                                                                                                                                (LockableFeature
                                                                                                                                   SelfDeletingMessagesConfig))
                                                                                                                        :<|> (Named
                                                                                                                                '("iput",
                                                                                                                                  SelfDeletingMessagesConfig)
                                                                                                                                (TeamId
                                                                                                                                 -> Feature
                                                                                                                                      SelfDeletingMessagesConfig
                                                                                                                                 -> 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]
                                                                                                                                      (LockableFeature
                                                                                                                                         SelfDeletingMessagesConfig))
                                                                                                                              :<|> Named
                                                                                                                                     '("ipatch",
                                                                                                                                       SelfDeletingMessagesConfig)
                                                                                                                                     (TeamId
                                                                                                                                      -> LockableFeaturePatch
                                                                                                                                           SelfDeletingMessagesConfig
                                                                                                                                      -> 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]
                                                                                                                                           (LockableFeature
                                                                                                                                              SelfDeletingMessagesConfig))))
                                                                                                                       :<|> ((Named
                                                                                                                                '("iget",
                                                                                                                                  GuestLinksConfig)
                                                                                                                                (TeamId
                                                                                                                                 -> 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]
                                                                                                                                      (LockableFeature
                                                                                                                                         GuestLinksConfig))
                                                                                                                              :<|> (Named
                                                                                                                                      '("iput",
                                                                                                                                        GuestLinksConfig)
                                                                                                                                      (TeamId
                                                                                                                                       -> Feature
                                                                                                                                            GuestLinksConfig
                                                                                                                                       -> 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]
                                                                                                                                            (LockableFeature
                                                                                                                                               GuestLinksConfig))
                                                                                                                                    :<|> Named
                                                                                                                                           '("ipatch",
                                                                                                                                             GuestLinksConfig)
                                                                                                                                           (TeamId
                                                                                                                                            -> LockableFeaturePatch
                                                                                                                                                 GuestLinksConfig
                                                                                                                                            -> 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]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    GuestLinksConfig))))
                                                                                                                             :<|> ((Named
                                                                                                                                      '("iget",
                                                                                                                                        SndFactorPasswordChallengeConfig)
                                                                                                                                      (TeamId
                                                                                                                                       -> 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]
                                                                                                                                            (LockableFeature
                                                                                                                                               SndFactorPasswordChallengeConfig))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("iput",
                                                                                                                                              SndFactorPasswordChallengeConfig)
                                                                                                                                            (TeamId
                                                                                                                                             -> Feature
                                                                                                                                                  SndFactorPasswordChallengeConfig
                                                                                                                                             -> 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]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     SndFactorPasswordChallengeConfig))
                                                                                                                                          :<|> Named
                                                                                                                                                 '("ipatch",
                                                                                                                                                   SndFactorPasswordChallengeConfig)
                                                                                                                                                 (TeamId
                                                                                                                                                  -> LockableFeaturePatch
                                                                                                                                                       SndFactorPasswordChallengeConfig
                                                                                                                                                  -> 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]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          SndFactorPasswordChallengeConfig))))
                                                                                                                                   :<|> ((Named
                                                                                                                                            '("iget",
                                                                                                                                              MLSConfig)
                                                                                                                                            (TeamId
                                                                                                                                             -> 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]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     MLSConfig))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("iput",
                                                                                                                                                    MLSConfig)
                                                                                                                                                  (TeamId
                                                                                                                                                   -> Feature
                                                                                                                                                        MLSConfig
                                                                                                                                                   -> 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]
                                                                                                                                                        (LockableFeature
                                                                                                                                                           MLSConfig))
                                                                                                                                                :<|> Named
                                                                                                                                                       '("ipatch",
                                                                                                                                                         MLSConfig)
                                                                                                                                                       (TeamId
                                                                                                                                                        -> LockableFeaturePatch
                                                                                                                                                             MLSConfig
                                                                                                                                                        -> 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]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                MLSConfig))))
                                                                                                                                         :<|> ((Named
                                                                                                                                                  '("iget",
                                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                  (TeamId
                                                                                                                                                   -> 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]
                                                                                                                                                        (LockableFeature
                                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("iput",
                                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                        (TeamId
                                                                                                                                                         -> Feature
                                                                                                                                                              ExposeInvitationURLsToTeamAdminConfig
                                                                                                                                                         -> 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]
                                                                                                                                                              (LockableFeature
                                                                                                                                                                 ExposeInvitationURLsToTeamAdminConfig))
                                                                                                                                                      :<|> Named
                                                                                                                                                             '("ipatch",
                                                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                             (TeamId
                                                                                                                                                              -> LockableFeaturePatch
                                                                                                                                                                   ExposeInvitationURLsToTeamAdminConfig
                                                                                                                                                              -> 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]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig))))
                                                                                                                                               :<|> ((Named
                                                                                                                                                        '("iget",
                                                                                                                                                          OutlookCalIntegrationConfig)
                                                                                                                                                        (TeamId
                                                                                                                                                         -> 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]
                                                                                                                                                              (LockableFeature
                                                                                                                                                                 OutlookCalIntegrationConfig))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("iput",
                                                                                                                                                                OutlookCalIntegrationConfig)
                                                                                                                                                              (TeamId
                                                                                                                                                               -> Feature
                                                                                                                                                                    OutlookCalIntegrationConfig
                                                                                                                                                               -> 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]
                                                                                                                                                                    (LockableFeature
                                                                                                                                                                       OutlookCalIntegrationConfig))
                                                                                                                                                            :<|> Named
                                                                                                                                                                   '("ipatch",
                                                                                                                                                                     OutlookCalIntegrationConfig)
                                                                                                                                                                   (TeamId
                                                                                                                                                                    -> LockableFeaturePatch
                                                                                                                                                                         OutlookCalIntegrationConfig
                                                                                                                                                                    -> 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]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            OutlookCalIntegrationConfig))))
                                                                                                                                                     :<|> ((Named
                                                                                                                                                              '("iget",
                                                                                                                                                                MlsE2EIdConfig)
                                                                                                                                                              (TeamId
                                                                                                                                                               -> 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]
                                                                                                                                                                    (LockableFeature
                                                                                                                                                                       MlsE2EIdConfig))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("iput",
                                                                                                                                                                      MlsE2EIdConfig)
                                                                                                                                                                    (TeamId
                                                                                                                                                                     -> Feature
                                                                                                                                                                          MlsE2EIdConfig
                                                                                                                                                                     -> 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]
                                                                                                                                                                          (LockableFeature
                                                                                                                                                                             MlsE2EIdConfig))
                                                                                                                                                                  :<|> Named
                                                                                                                                                                         '("ipatch",
                                                                                                                                                                           MlsE2EIdConfig)
                                                                                                                                                                         (TeamId
                                                                                                                                                                          -> LockableFeaturePatch
                                                                                                                                                                               MlsE2EIdConfig
                                                                                                                                                                          -> 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]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  MlsE2EIdConfig))))
                                                                                                                                                           :<|> ((Named
                                                                                                                                                                    '("iget",
                                                                                                                                                                      MlsMigrationConfig)
                                                                                                                                                                    (TeamId
                                                                                                                                                                     -> 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]
                                                                                                                                                                          (LockableFeature
                                                                                                                                                                             MlsMigrationConfig))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("iput",
                                                                                                                                                                            MlsMigrationConfig)
                                                                                                                                                                          (TeamId
                                                                                                                                                                           -> Feature
                                                                                                                                                                                MlsMigrationConfig
                                                                                                                                                                           -> 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]
                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                   MlsMigrationConfig))
                                                                                                                                                                        :<|> Named
                                                                                                                                                                               '("ipatch",
                                                                                                                                                                                 MlsMigrationConfig)
                                                                                                                                                                               (TeamId
                                                                                                                                                                                -> LockableFeaturePatch
                                                                                                                                                                                     MlsMigrationConfig
                                                                                                                                                                                -> 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]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        MlsMigrationConfig))))
                                                                                                                                                                 :<|> ((Named
                                                                                                                                                                          '("iget",
                                                                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                                                                          (TeamId
                                                                                                                                                                           -> 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]
                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                   EnforceFileDownloadLocationConfig))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("iput",
                                                                                                                                                                                  EnforceFileDownloadLocationConfig)
                                                                                                                                                                                (TeamId
                                                                                                                                                                                 -> Feature
                                                                                                                                                                                      EnforceFileDownloadLocationConfig
                                                                                                                                                                                 -> 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]
                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                         EnforceFileDownloadLocationConfig))
                                                                                                                                                                              :<|> Named
                                                                                                                                                                                     '("ipatch",
                                                                                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                                                                                     (TeamId
                                                                                                                                                                                      -> LockableFeaturePatch
                                                                                                                                                                                           EnforceFileDownloadLocationConfig
                                                                                                                                                                                      -> 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]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              EnforceFileDownloadLocationConfig))))
                                                                                                                                                                       :<|> (Named
                                                                                                                                                                               '("iget",
                                                                                                                                                                                 LimitedEventFanoutConfig)
                                                                                                                                                                               (TeamId
                                                                                                                                                                                -> 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]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        LimitedEventFanoutConfig))
                                                                                                                                                                             :<|> (Named
                                                                                                                                                                                     '("iput",
                                                                                                                                                                                       LimitedEventFanoutConfig)
                                                                                                                                                                                     (TeamId
                                                                                                                                                                                      -> Feature
                                                                                                                                                                                           LimitedEventFanoutConfig
                                                                                                                                                                                      -> 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]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              LimitedEventFanoutConfig))
                                                                                                                                                                                   :<|> Named
                                                                                                                                                                                          '("ipatch",
                                                                                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                                                                                          (TeamId
                                                                                                                                                                                           -> LockableFeaturePatch
                                                                                                                                                                                                LimitedEventFanoutConfig
                                                                                                                                                                                           -> 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]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   LimitedEventFanoutConfig)))))))))))))))))))))))
                                                          :<|> (Named
                                                                  '("ilock", FileSharingConfig)
                                                                  (TeamId
                                                                   -> LockStatus
                                                                   -> 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]
                                                                        LockStatusResponse)
                                                                :<|> (Named
                                                                        '("ilock",
                                                                          ConferenceCallingConfig)
                                                                        (TeamId
                                                                         -> LockStatus
                                                                         -> 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]
                                                                              LockStatusResponse)
                                                                      :<|> (Named
                                                                              '("ilock",
                                                                                SelfDeletingMessagesConfig)
                                                                              (TeamId
                                                                               -> LockStatus
                                                                               -> 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]
                                                                                    LockStatusResponse)
                                                                            :<|> (Named
                                                                                    '("ilock",
                                                                                      GuestLinksConfig)
                                                                                    (TeamId
                                                                                     -> LockStatus
                                                                                     -> 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]
                                                                                          LockStatusResponse)
                                                                                  :<|> (Named
                                                                                          '("ilock",
                                                                                            SndFactorPasswordChallengeConfig)
                                                                                          (TeamId
                                                                                           -> LockStatus
                                                                                           -> 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]
                                                                                                LockStatusResponse)
                                                                                        :<|> (Named
                                                                                                '("ilock",
                                                                                                  MLSConfig)
                                                                                                (TeamId
                                                                                                 -> LockStatus
                                                                                                 -> 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]
                                                                                                      LockStatusResponse)
                                                                                              :<|> (Named
                                                                                                      '("ilock",
                                                                                                        OutlookCalIntegrationConfig)
                                                                                                      (TeamId
                                                                                                       -> LockStatus
                                                                                                       -> 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]
                                                                                                            LockStatusResponse)
                                                                                                    :<|> (Named
                                                                                                            '("ilock",
                                                                                                              MlsE2EIdConfig)
                                                                                                            (TeamId
                                                                                                             -> LockStatus
                                                                                                             -> 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]
                                                                                                                  LockStatusResponse)
                                                                                                          :<|> (Named
                                                                                                                  '("ilock",
                                                                                                                    MlsMigrationConfig)
                                                                                                                  (TeamId
                                                                                                                   -> LockStatus
                                                                                                                   -> 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]
                                                                                                                        LockStatusResponse)
                                                                                                                :<|> (Named
                                                                                                                        '("ilock",
                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                        (TeamId
                                                                                                                         -> LockStatus
                                                                                                                         -> 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]
                                                                                                                              LockStatusResponse)
                                                                                                                      :<|> (Named
                                                                                                                              '("igetmulti",
                                                                                                                                SearchVisibilityInboundConfig)
                                                                                                                              (TeamFeatureNoConfigMultiRequest
                                                                                                                               -> 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]
                                                                                                                                    (TeamFeatureNoConfigMultiResponse
                                                                                                                                       SearchVisibilityInboundConfig))
                                                                                                                            :<|> Named
                                                                                                                                   "feature-configs-internal"
                                                                                                                                   (Maybe
                                                                                                                                      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]
                                                                                                                                         AllTeamFeatures)))))))))))))
                                                         :<|> (Named
                                                                 "get-federation-status"
                                                                 (QualifiedWithTag 'QLocal UserId
                                                                  -> RemoteDomains
                                                                  -> 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]
                                                                       FederationStatus)
                                                               :<|> ((Named
                                                                        "conversation-get-member"
                                                                        (ConvId
                                                                         -> 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]
                                                                              (Maybe Member))
                                                                      :<|> (Named
                                                                              "conversation-accept-v2"
                                                                              (QualifiedWithTag
                                                                                 'QLocal UserId
                                                                               -> Maybe ConnId
                                                                               -> 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]
                                                                                    Conversation)
                                                                            :<|> (Named
                                                                                    "conversation-block-unqualified"
                                                                                    (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]
                                                                                          ())
                                                                                  :<|> (Named
                                                                                          "conversation-block"
                                                                                          (QualifiedWithTag
                                                                                             'QLocal
                                                                                             UserId
                                                                                           -> Qualified
                                                                                                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]
                                                                                                ())
                                                                                        :<|> (Named
                                                                                                "conversation-unblock-unqualified"
                                                                                                (QualifiedWithTag
                                                                                                   'QLocal
                                                                                                   UserId
                                                                                                 -> Maybe
                                                                                                      ConnId
                                                                                                 -> 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]
                                                                                                      Conversation)
                                                                                              :<|> (Named
                                                                                                      "conversation-unblock"
                                                                                                      (QualifiedWithTag
                                                                                                         'QLocal
                                                                                                         UserId
                                                                                                       -> Maybe
                                                                                                            ConnId
                                                                                                       -> Qualified
                                                                                                            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]
                                                                                                            ())
                                                                                                    :<|> (Named
                                                                                                            "conversation-meta"
                                                                                                            (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]
                                                                                                                  ConversationMetadata)
                                                                                                          :<|> (Named
                                                                                                                  "conversation-mls-one-to-one"
                                                                                                                  (QualifiedWithTag
                                                                                                                     'QLocal
                                                                                                                     UserId
                                                                                                                   -> Qualified
                                                                                                                        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]
                                                                                                                        Conversation)
                                                                                                                :<|> Named
                                                                                                                       "conversation-mls-one-to-one-established"
                                                                                                                       (QualifiedWithTag
                                                                                                                          'QLocal
                                                                                                                          UserId
                                                                                                                        -> Qualified
                                                                                                                             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]
                                                                                                                             Bool)))))))))
                                                                     :<|> Named
                                                                            "get-conversations-by-user"
                                                                            (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]
                                                                                  [EJPDConvInfo]))))))))))))
ServerT
  InternalAPIBase
  (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])
-> ServerT InternalAPI (Sem GalleyEffects)
forall a. a -> a
Imports.id (API
   InternalAPIBase
   '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
     Rpc, ExternalAccess, FederatorAccess,
     BackendNotificationQueueAccess, BotAccess, FireAndForget,
     ClientStore, CodeStore, ProposalStore, ConversationStore,
     SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
     LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
     TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
     TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
     ListItems CassandraPaging (Remote ConvId),
     ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
     ListItems InternalPaging TeamId, Input AllTeamFeatures,
     Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
     Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
     Logger (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 InternalAPI GalleyEffects)
-> API
     InternalAPIBase
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 InternalAPI GalleyEffects
forall a b. (a -> b) -> a -> b
$
    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 @"status" (()
-> 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]
     ()
forall a.
a
-> 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]
     a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
      API
  (Named
     "status"
     ("status" :> MultiVerb 'GET '[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-user"
        (Summary
           "Remove a user from their teams and conversations and erase their clients"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (ZLocalUser
                     :> (ZOptConn
                         :> ("user"
                             :> MultiVerb
                                  'DELETE
                                  '[JSON]
                                  '[RespondEmpty 200 "Remove a user from Galley"]
                                  ()))))))
      :<|> (Named
              "connect"
              (Summary "Create a connect conversation (deprecated)"
               :> (MakesFederatedCall 'Brig "api-version"
                   :> (MakesFederatedCall 'Galley "on-conversation-created"
                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'InvalidOperation
                                   :> (CanThrow 'NotConnected
                                       :> (CanThrow UnreachableBackends
                                           :> (ZLocalUser
                                               :> (ZOptConn
                                                   :> ("conversations"
                                                       :> ("connect"
                                                           :> (ReqBody '[JSON] Connect
                                                               :> 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-conversation-clients"
                    (Summary "Get mls conversation client list"
                     :> (CanThrow 'ConvNotFound
                         :> ("group"
                             :> (Capture "gid" GroupId
                                 :> MultiVerb
                                      'GET
                                      '[JSON]
                                      '[Respond 200 "Clients" ClientList]
                                      ClientList))))
                  :<|> (Named
                          "guard-legalhold-policy-conflicts"
                          ("guard-legalhold-policy-conflicts"
                           :> (CanThrow 'MissingLegalholdConsent
                               :> (CanThrow 'MissingLegalholdConsentOldClients
                                   :> (ReqBody '[JSON] GuardLegalholdPolicyConflicts
                                       :> MultiVerb
                                            'PUT
                                            '[JSON]
                                            '[RespondEmpty 200 "Guard Legalhold Policy"]
                                            ()))))
                        :<|> (("legalhold"
                               :> ("whitelisted-teams"
                                   :> (Capture "tid" TeamId
                                       :> (Named
                                             "set-team-legalhold-whitelisted"
                                             (MultiVerb
                                                'PUT
                                                '[JSON]
                                                '[RespondEmpty 200 "Team Legalhold Whitelisted"]
                                                ())
                                           :<|> (Named
                                                   "unset-team-legalhold-whitelisted"
                                                   (MultiVerb
                                                      'DELETE
                                                      '[JSON]
                                                      '[RespondEmpty
                                                          204 "Team Legalhold un-Whitelisted"]
                                                      ())
                                                 :<|> Named
                                                        "get-team-legalhold-whitelisted"
                                                        (MultiVerb
                                                           'GET
                                                           '[JSON]
                                                           '[RespondEmpty
                                                               404 "Team not Legalhold Whitelisted",
                                                             RespondEmpty
                                                               200 "Team Legalhold Whitelisted"]
                                                           Bool))))))
                              :<|> (("teams"
                                     :> (Capture "tid" TeamId
                                         :> (Named
                                               "get-team-internal"
                                               (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
                                             :<|> (Named
                                                     "create-binding-team"
                                                     (ZUser
                                                      :> (ReqBody '[JSON] BindingNewTeam
                                                          :> MultiVerb
                                                               'PUT
                                                               '[JSON]
                                                               '[WithHeaders
                                                                   '[Header "Location" TeamId]
                                                                   TeamId
                                                                   (RespondEmpty 201 "OK")]
                                                               TeamId))
                                                   :<|> (Named
                                                           "delete-binding-team"
                                                           (CanThrow 'NoBindingTeam
                                                            :> (CanThrow 'NotAOneMemberTeam
                                                                :> (CanThrow 'DeleteQueueFull
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> (QueryFlag "force"
                                                                            :> MultiVerb
                                                                                 'DELETE
                                                                                 '[JSON]
                                                                                 '[RespondEmpty
                                                                                     202 "OK"]
                                                                                 ())))))
                                                         :<|> (Named
                                                                 "get-team-name"
                                                                 ("name"
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> Get '[JSON] TeamName))
                                                               :<|> (Named
                                                                       "update-team-status"
                                                                       ("status"
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  'InvalidTeamStatusUpdate
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      TeamStatusUpdate
                                                                                    :> MultiVerb
                                                                                         'PUT
                                                                                         '[JSON]
                                                                                         '[RespondEmpty
                                                                                             200
                                                                                             "OK"]
                                                                                         ()))))
                                                                     :<|> (("members"
                                                                            :> (Named
                                                                                  "unchecked-add-team-member"
                                                                                  (CanThrow
                                                                                     'TooManyTeamMembers
                                                                                   :> (CanThrow
                                                                                         'TooManyTeamMembersOnTeamWithLegalhold
                                                                                       :> (CanThrow
                                                                                             'TooManyTeamAdmins
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 NewTeamMember
                                                                                               :> MultiVerb
                                                                                                    'POST
                                                                                                    '[JSON]
                                                                                                    '[RespondEmpty
                                                                                                        200
                                                                                                        "OK"]
                                                                                                    ()))))
                                                                                :<|> (Named
                                                                                        "unchecked-get-team-members"
                                                                                        (QueryParam'
                                                                                           '[Strict]
                                                                                           "maxResults"
                                                                                           (Range
                                                                                              1
                                                                                              HardTruncationLimit
                                                                                              Int32)
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              TeamMemberList)
                                                                                      :<|> (Named
                                                                                              "unchecked-get-team-member"
                                                                                              (Capture
                                                                                                 "uid"
                                                                                                 UserId
                                                                                               :> (CanThrow
                                                                                                     'TeamMemberNotFound
                                                                                                   :> Get
                                                                                                        '[JSON]
                                                                                                        TeamMember))
                                                                                            :<|> (Named
                                                                                                    "can-user-join-team"
                                                                                                    ("check"
                                                                                                     :> (CanThrow
                                                                                                           'TooManyTeamMembersOnTeamWithLegalhold
                                                                                                         :> MultiVerb
                                                                                                              'GET
                                                                                                              '[JSON]
                                                                                                              '[RespondEmpty
                                                                                                                  200
                                                                                                                  "User can join"]
                                                                                                              ()))
                                                                                                  :<|> Named
                                                                                                         "unchecked-update-team-member"
                                                                                                         (CanThrow
                                                                                                            'AccessDenied
                                                                                                          :> (CanThrow
                                                                                                                'InvalidPermissions
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamMemberNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            'TooManyTeamAdmins
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    ('MissingPermission
                                                                                                                                       'Nothing)
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        NewTeamMember
                                                                                                                                      :> MultiVerb
                                                                                                                                           'PUT
                                                                                                                                           '[JSON]
                                                                                                                                           '[RespondEmpty
                                                                                                                                               200
                                                                                                                                               ""]
                                                                                                                                           ())))))))))))))
                                                                           :<|> (Named
                                                                                   "user-is-team-owner"
                                                                                   ("is-team-owner"
                                                                                    :> (Capture
                                                                                          "uid"
                                                                                          UserId
                                                                                        :> (CanThrow
                                                                                              'AccessDenied
                                                                                            :> (CanThrow
                                                                                                  'TeamMemberNotFound
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> MultiVerb
                                                                                                         'GET
                                                                                                         '[JSON]
                                                                                                         '[RespondEmpty
                                                                                                             200
                                                                                                             "User is team owner"]
                                                                                                         ())))))
                                                                                 :<|> ("search-visibility"
                                                                                       :> (Named
                                                                                             "get-search-visibility-internal"
                                                                                             (Get
                                                                                                '[JSON]
                                                                                                TeamSearchVisibilityView)
                                                                                           :<|> Named
                                                                                                  "set-search-visibility-internal"
                                                                                                  (CanThrow
                                                                                                     'TeamSearchVisibilityNotEnabled
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     TeamSearchVisibilityView
                                                                                                                   :> MultiVerb
                                                                                                                        'PUT
                                                                                                                        '[JSON]
                                                                                                                        '[RespondEmpty
                                                                                                                            204
                                                                                                                            "OK"]
                                                                                                                        ()))))))))))))))))
                                    :<|> ((Named
                                             "get-team-members"
                                             (CanThrow 'NonBindingTeam
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("users"
                                                      :> (Capture "uid" UserId
                                                          :> ("team"
                                                              :> ("members"
                                                                  :> Get
                                                                       '[JSON] TeamMemberList))))))
                                           :<|> (Named
                                                   "get-team-id"
                                                   (CanThrow 'NonBindingTeam
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("users"
                                                            :> (Capture "uid" UserId
                                                                :> ("team"
                                                                    :> Get '[JSON] TeamId)))))
                                                 :<|> (Named
                                                         "test-get-clients"
                                                         ("test"
                                                          :> ("clients"
                                                              :> (ZUser :> Get '[JSON] [ClientId])))
                                                       :<|> (Named
                                                               "test-add-client"
                                                               ("clients"
                                                                :> (ZUser
                                                                    :> (Capture "cid" ClientId
                                                                        :> MultiVerb
                                                                             'POST
                                                                             '[JSON]
                                                                             '[RespondEmpty
                                                                                 200 "OK"]
                                                                             ())))
                                                             :<|> (Named
                                                                     "test-delete-client"
                                                                     ("clients"
                                                                      :> (ZUser
                                                                          :> (Capture "cid" ClientId
                                                                              :> MultiVerb
                                                                                   'DELETE
                                                                                   '[JSON]
                                                                                   '[RespondEmpty
                                                                                       200 "OK"]
                                                                                   ())))
                                                                   :<|> (Named
                                                                           "add-service"
                                                                           ("services"
                                                                            :> (ReqBody
                                                                                  '[JSON] Service
                                                                                :> MultiVerb
                                                                                     'POST
                                                                                     '[JSON]
                                                                                     '[RespondEmpty
                                                                                         200 "OK"]
                                                                                     ()))
                                                                         :<|> (Named
                                                                                 "delete-service"
                                                                                 ("services"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        ServiceRef
                                                                                      :> MultiVerb
                                                                                           'DELETE
                                                                                           '[JSON]
                                                                                           '[RespondEmpty
                                                                                               200
                                                                                               "OK"]
                                                                                           ()))
                                                                               :<|> (Named
                                                                                       "i-add-bot"
                                                                                       (CanThrow
                                                                                          ('ActionDenied
                                                                                             'AddConversationMember)
                                                                                        :> (CanThrow
                                                                                              'ConvNotFound
                                                                                            :> (CanThrow
                                                                                                  'InvalidOperation
                                                                                                :> (CanThrow
                                                                                                      'TooManyMembers
                                                                                                    :> ("bots"
                                                                                                        :> (ZLocalUser
                                                                                                            :> (ZConn
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      AddBot
                                                                                                                    :> Post
                                                                                                                         '[JSON]
                                                                                                                         Event))))))))
                                                                                     :<|> (Named
                                                                                             "delete-bot"
                                                                                             (CanThrow
                                                                                                'ConvNotFound
                                                                                              :> (CanThrow
                                                                                                    ('ActionDenied
                                                                                                       'RemoveConversationMember)
                                                                                                  :> ("bots"
                                                                                                      :> (ZLocalUser
                                                                                                          :> (ZOptConn
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    RemoveBot
                                                                                                                  :> MultiVerb
                                                                                                                       'DELETE
                                                                                                                       '[JSON]
                                                                                                                       (UpdateResponses
                                                                                                                          "Bot not found"
                                                                                                                          "Bot deleted"
                                                                                                                          Event)
                                                                                                                       (UpdateResult
                                                                                                                          Event)))))))
                                                                                           :<|> (Named
                                                                                                   "put-custom-backend"
                                                                                                   ("custom-backend"
                                                                                                    :> ("by-domain"
                                                                                                        :> (Capture
                                                                                                              "domain"
                                                                                                              Domain
                                                                                                            :> (ReqBody
                                                                                                                  '[JSON]
                                                                                                                  CustomBackend
                                                                                                                :> MultiVerb
                                                                                                                     'PUT
                                                                                                                     '[JSON]
                                                                                                                     '[RespondEmpty
                                                                                                                         201
                                                                                                                         "OK"]
                                                                                                                     ()))))
                                                                                                 :<|> Named
                                                                                                        "delete-custom-backend"
                                                                                                        ("custom-backend"
                                                                                                         :> ("by-domain"
                                                                                                             :> (Capture
                                                                                                                   "domain"
                                                                                                                   Domain
                                                                                                                 :> MultiVerb
                                                                                                                      'DELETE
                                                                                                                      '[JSON]
                                                                                                                      '[RespondEmpty
                                                                                                                          200
                                                                                                                          "OK"]
                                                                                                                      ())))))))))))))
                                          :<|> (Named
                                                  "upsert-one2one"
                                                  (Summary
                                                     "Create or Update a connect or one2one conversation."
                                                   :> ("conversations"
                                                       :> ("one2one"
                                                           :> ("upsert"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     UpsertOne2OneConversationRequest
                                                                   :> MultiVerb
                                                                        'POST
                                                                        '[JSON]
                                                                        '[RespondEmpty
                                                                            200
                                                                            "Upsert One2One Policy"]
                                                                        ())))))
                                                :<|> ((((Named
                                                           '("iget", LegalholdConfig)
                                                           (Description ""
                                                            :> (Summary "Get config for legalhold"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("legalhold"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    LegalholdConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput", LegalholdConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Put config for legalhold"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[ 'ActionDenied
                                                                                                 'RemoveConversationMember,
                                                                                               'CannotEnableLegalHoldServiceLargeTeam,
                                                                                               'LegalHoldNotEnabled,
                                                                                               'LegalHoldDisableUnimplemented,
                                                                                               'LegalHoldServiceNotRegistered,
                                                                                               'UserLegalHoldIllegalOperation,
                                                                                               'LegalHoldCouldNotBlockConnections]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("legalhold"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   LegalholdConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      LegalholdConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch", LegalholdConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for legalhold"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[ 'ActionDenied
                                                                                                      'RemoveConversationMember,
                                                                                                    'CannotEnableLegalHoldServiceLargeTeam,
                                                                                                    'LegalHoldNotEnabled,
                                                                                                    'LegalHoldDisableUnimplemented,
                                                                                                    'LegalHoldServiceNotRegistered,
                                                                                                    'UserLegalHoldIllegalOperation,
                                                                                                    'LegalHoldCouldNotBlockConnections]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("legalhold"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        LegalholdConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           LegalholdConfig)))))))))))))))
                                                        :<|> ((Named
                                                                 '("iget", SSOConfig)
                                                                 (Description ""
                                                                  :> (Summary "Get config for sso"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("sso"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          SSOConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput", SSOConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for sso"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("sso"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         SSOConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            SSOConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch", SSOConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for sso"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("sso"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              SSOConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 SSOConfig)))))))))))))))
                                                              :<|> ((Named
                                                                       '("iget",
                                                                         SearchVisibilityAvailableConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for searchVisibility"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("searchVisibility"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SearchVisibilityAvailableConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               SearchVisibilityAvailableConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for searchVisibility"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("searchVisibility"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               SearchVisibilityAvailableConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  SearchVisibilityAvailableConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    SearchVisibilityAvailableConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for searchVisibility"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("searchVisibility"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    SearchVisibilityAvailableConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       SearchVisibilityAvailableConfig)))))))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               SearchVisibilityInboundConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for searchVisibilityInbound"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("searchVisibilityInbound"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      SearchVisibilityInboundConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     SearchVisibilityInboundConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for searchVisibilityInbound"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("searchVisibilityInbound"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     SearchVisibilityInboundConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        SearchVisibilityInboundConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          SearchVisibilityInboundConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for searchVisibilityInbound"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("searchVisibilityInbound"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          SearchVisibilityInboundConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             SearchVisibilityInboundConfig)))))))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     ValidateSAMLEmailsConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for validateSAMLemails"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("validateSAMLemails"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            ValidateSAMLEmailsConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           ValidateSAMLEmailsConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for validateSAMLemails"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("validateSAMLemails"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           ValidateSAMLEmailsConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              ValidateSAMLEmailsConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                ValidateSAMLEmailsConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for validateSAMLemails"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("validateSAMLemails"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                ValidateSAMLEmailsConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   ValidateSAMLEmailsConfig)))))))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           DigitalSignaturesConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for digitalSignatures"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("digitalSignatures"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  DigitalSignaturesConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 DigitalSignaturesConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for digitalSignatures"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("digitalSignatures"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 DigitalSignaturesConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    DigitalSignaturesConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      DigitalSignaturesConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for digitalSignatures"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("digitalSignatures"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      DigitalSignaturesConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         DigitalSignaturesConfig)))))))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 AppLockConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for appLock"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("appLock"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        AppLockConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       AppLockConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for appLock"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("appLock"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       AppLockConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          AppLockConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            AppLockConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for appLock"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("appLock"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            AppLockConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               AppLockConfig)))))))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       FileSharingConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for fileSharing"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("fileSharing"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              FileSharingConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             FileSharingConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for fileSharing"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("fileSharing"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             FileSharingConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                FileSharingConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  FileSharingConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for fileSharing"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("fileSharing"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  FileSharingConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     FileSharingConfig)))))))))))))))
                                                                                                  :<|> (Named
                                                                                                          '("iget",
                                                                                                            ClassifiedDomainsConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Get config for classifiedDomains"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("classifiedDomains"
                                                                                                                                           :> Get
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   ClassifiedDomainsConfig))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   ConferenceCallingConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for conferenceCalling"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("conferenceCalling"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          ConferenceCallingConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         ConferenceCallingConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for conferenceCalling"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("conferenceCalling"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         ConferenceCallingConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            ConferenceCallingConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              ConferenceCallingConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for conferenceCalling"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("conferenceCalling"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              ConferenceCallingConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 ConferenceCallingConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         SelfDeletingMessagesConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for selfDeletingMessages"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("selfDeletingMessages"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                SelfDeletingMessagesConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               SelfDeletingMessagesConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for selfDeletingMessages"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("selfDeletingMessages"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               SelfDeletingMessagesConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  SelfDeletingMessagesConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    SelfDeletingMessagesConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for selfDeletingMessages"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("selfDeletingMessages"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    SelfDeletingMessagesConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       SelfDeletingMessagesConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               GuestLinksConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for conversationGuestLinks"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("conversationGuestLinks"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      GuestLinksConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     GuestLinksConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for conversationGuestLinks"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("conversationGuestLinks"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     GuestLinksConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        GuestLinksConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          GuestLinksConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for conversationGuestLinks"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          GuestLinksConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             GuestLinksConfig)))))))))))))))
                                                                                                                          :<|> ((Named
                                                                                                                                   '("iget",
                                                                                                                                     SndFactorPasswordChallengeConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for sndFactorPasswordChallenge"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("sndFactorPasswordChallenge"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                 :<|> (Named
                                                                                                                                         '("iput",
                                                                                                                                           SndFactorPasswordChallengeConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Put config for sndFactorPasswordChallenge"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Feature
                                                                                                                                                                                           SndFactorPasswordChallengeConfig)
                                                                                                                                                                                      :> Put
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              SndFactorPasswordChallengeConfig)))))))))))))
                                                                                                                                       :<|> Named
                                                                                                                                              '("ipatch",
                                                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Patch config for sndFactorPasswordChallenge"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                                                                :<|> ((Named
                                                                                                                                         '("iget",
                                                                                                                                           MLSConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for mls"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("mls"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  MLSConfig))))))))))
                                                                                                                                       :<|> (Named
                                                                                                                                               '("iput",
                                                                                                                                                 MLSConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Put config for mls"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                          '[]
                                                                                                                                                                        :> ("teams"
                                                                                                                                                                            :> (Capture
                                                                                                                                                                                  "tid"
                                                                                                                                                                                  TeamId
                                                                                                                                                                                :> ("features"
                                                                                                                                                                                    :> ("mls"
                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (Feature
                                                                                                                                                                                                 MLSConfig)
                                                                                                                                                                                            :> Put
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    MLSConfig)))))))))))))
                                                                                                                                             :<|> Named
                                                                                                                                                    '("ipatch",
                                                                                                                                                      MLSConfig)
                                                                                                                                                    (Description
                                                                                                                                                       ""
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Patch config for mls"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("mls"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                                                      MLSConfig)
                                                                                                                                                                                                 :> Patch
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         MLSConfig)))))))))))))))
                                                                                                                                      :<|> ((Named
                                                                                                                                               '("iget",
                                                                                                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                                                             :<|> (Named
                                                                                                                                                     '("iput",
                                                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                          :> (CanThrowMany
                                                                                                                                                                                '[]
                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                        "tid"
                                                                                                                                                                                        TeamId
                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (Feature
                                                                                                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                                  :> Put
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                                                                   :<|> Named
                                                                                                                                                          '("ipatch",
                                                                                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                          (Description
                                                                                                                                                             ""
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('MissingPermission
                                                                                                                                                                        'Nothing)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 TeamFeatureError
                                                                                                                                                                               :> (CanThrowMany
                                                                                                                                                                                     '[]
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                                       :> Patch
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                                                            :<|> ((Named
                                                                                                                                                     '("iget",
                                                                                                                                                       OutlookCalIntegrationConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Get config for outlookCalIntegration"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("outlookCalIntegration"
                                                                                                                                                                                      :> Get
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              OutlookCalIntegrationConfig))))))))))
                                                                                                                                                   :<|> (Named
                                                                                                                                                           '("iput",
                                                                                                                                                             OutlookCalIntegrationConfig)
                                                                                                                                                           (Description
                                                                                                                                                              ""
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Put config for outlookCalIntegration"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  TeamFeatureError
                                                                                                                                                                                :> (CanThrowMany
                                                                                                                                                                                      '[]
                                                                                                                                                                                    :> ("teams"
                                                                                                                                                                                        :> (Capture
                                                                                                                                                                                              "tid"
                                                                                                                                                                                              TeamId
                                                                                                                                                                                            :> ("features"
                                                                                                                                                                                                :> ("outlookCalIntegration"
                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (Feature
                                                                                                                                                                                                             OutlookCalIntegrationConfig)
                                                                                                                                                                                                        :> Put
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                OutlookCalIntegrationConfig)))))))))))))
                                                                                                                                                         :<|> Named
                                                                                                                                                                '("ipatch",
                                                                                                                                                                  OutlookCalIntegrationConfig)
                                                                                                                                                                (Description
                                                                                                                                                                   ""
                                                                                                                                                                 :> (Summary
                                                                                                                                                                       "Patch config for outlookCalIntegration"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('MissingPermission
                                                                                                                                                                              'Nothing)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       TeamFeatureError
                                                                                                                                                                                     :> (CanThrowMany
                                                                                                                                                                                           '[]
                                                                                                                                                                                         :> ("teams"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "tid"
                                                                                                                                                                                                   TeamId
                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                     :> ("outlookCalIntegration"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                                                                  OutlookCalIntegrationConfig)
                                                                                                                                                                                                             :> Patch
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     OutlookCalIntegrationConfig)))))))))))))))
                                                                                                                                                  :<|> ((Named
                                                                                                                                                           '("iget",
                                                                                                                                                             MlsE2EIdConfig)
                                                                                                                                                           (Description
                                                                                                                                                              ""
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Get config for mlsE2EId"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                :> (Capture
                                                                                                                                                                                      "tid"
                                                                                                                                                                                      TeamId
                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                        :> ("mlsE2EId"
                                                                                                                                                                                            :> Get
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    MlsE2EIdConfig))))))))))
                                                                                                                                                         :<|> (Named
                                                                                                                                                                 '("iput",
                                                                                                                                                                   MlsE2EIdConfig)
                                                                                                                                                                 (Description
                                                                                                                                                                    ""
                                                                                                                                                                  :> (Summary
                                                                                                                                                                        "Put config for mlsE2EId"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            ('MissingPermission
                                                                                                                                                                               'Nothing)
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        TeamFeatureError
                                                                                                                                                                                      :> (CanThrowMany
                                                                                                                                                                                            '[]
                                                                                                                                                                                          :> ("teams"
                                                                                                                                                                                              :> (Capture
                                                                                                                                                                                                    "tid"
                                                                                                                                                                                                    TeamId
                                                                                                                                                                                                  :> ("features"
                                                                                                                                                                                                      :> ("mlsE2EId"
                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (Feature
                                                                                                                                                                                                                   MlsE2EIdConfig)
                                                                                                                                                                                                              :> Put
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                                      MlsE2EIdConfig)))))))))))))
                                                                                                                                                               :<|> Named
                                                                                                                                                                      '("ipatch",
                                                                                                                                                                        MlsE2EIdConfig)
                                                                                                                                                                      (Description
                                                                                                                                                                         ""
                                                                                                                                                                       :> (Summary
                                                                                                                                                                             "Patch config for mlsE2EId"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('MissingPermission
                                                                                                                                                                                    'Nothing)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             TeamFeatureError
                                                                                                                                                                                           :> (CanThrowMany
                                                                                                                                                                                                 '[]
                                                                                                                                                                                               :> ("teams"
                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                         "tid"
                                                                                                                                                                                                         TeamId
                                                                                                                                                                                                       :> ("features"
                                                                                                                                                                                                           :> ("mlsE2EId"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                                                                        MlsE2EIdConfig)
                                                                                                                                                                                                                   :> Patch
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                           MlsE2EIdConfig)))))))))))))))
                                                                                                                                                        :<|> ((Named
                                                                                                                                                                 '("iget",
                                                                                                                                                                   MlsMigrationConfig)
                                                                                                                                                                 (Description
                                                                                                                                                                    ""
                                                                                                                                                                  :> (Summary
                                                                                                                                                                        "Get config for mlsMigration"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            ('MissingPermission
                                                                                                                                                                               'Nothing)
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> ("teams"
                                                                                                                                                                                      :> (Capture
                                                                                                                                                                                            "tid"
                                                                                                                                                                                            TeamId
                                                                                                                                                                                          :> ("features"
                                                                                                                                                                                              :> ("mlsMigration"
                                                                                                                                                                                                  :> Get
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          MlsMigrationConfig))))))))))
                                                                                                                                                               :<|> (Named
                                                                                                                                                                       '("iput",
                                                                                                                                                                         MlsMigrationConfig)
                                                                                                                                                                       (Description
                                                                                                                                                                          ""
                                                                                                                                                                        :> (Summary
                                                                                                                                                                              "Put config for mlsMigration"
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  ('MissingPermission
                                                                                                                                                                                     'Nothing)
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              TeamFeatureError
                                                                                                                                                                                            :> (CanThrowMany
                                                                                                                                                                                                  '[]
                                                                                                                                                                                                :> ("teams"
                                                                                                                                                                                                    :> (Capture
                                                                                                                                                                                                          "tid"
                                                                                                                                                                                                          TeamId
                                                                                                                                                                                                        :> ("features"
                                                                                                                                                                                                            :> ("mlsMigration"
                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (Feature
                                                                                                                                                                                                                         MlsMigrationConfig)
                                                                                                                                                                                                                    :> Put
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                                                            MlsMigrationConfig)))))))))))))
                                                                                                                                                                     :<|> Named
                                                                                                                                                                            '("ipatch",
                                                                                                                                                                              MlsMigrationConfig)
                                                                                                                                                                            (Description
                                                                                                                                                                               ""
                                                                                                                                                                             :> (Summary
                                                                                                                                                                                   "Patch config for mlsMigration"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('MissingPermission
                                                                                                                                                                                          'Nothing)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   TeamFeatureError
                                                                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                                                                       '[]
                                                                                                                                                                                                     :> ("teams"
                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                               "tid"
                                                                                                                                                                                                               TeamId
                                                                                                                                                                                                             :> ("features"
                                                                                                                                                                                                                 :> ("mlsMigration"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                                                                              MlsMigrationConfig)
                                                                                                                                                                                                                         :> Patch
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                 MlsMigrationConfig)))))))))))))))
                                                                                                                                                              :<|> ((Named
                                                                                                                                                                       '("iget",
                                                                                                                                                                         EnforceFileDownloadLocationConfig)
                                                                                                                                                                       (Description
                                                                                                                                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                        :> (Summary
                                                                                                                                                                              "Get config for enforceFileDownloadLocation"
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  ('MissingPermission
                                                                                                                                                                                     'Nothing)
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                        :> ("teams"
                                                                                                                                                                                            :> (Capture
                                                                                                                                                                                                  "tid"
                                                                                                                                                                                                  TeamId
                                                                                                                                                                                                :> ("features"
                                                                                                                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                        :> Get
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                                                     :<|> (Named
                                                                                                                                                                             '("iput",
                                                                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                                                                             (Description
                                                                                                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                              :> (Summary
                                                                                                                                                                                    "Put config for enforceFileDownloadLocation"
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        ('MissingPermission
                                                                                                                                                                                           'Nothing)
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    TeamFeatureError
                                                                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                                                                        '[]
                                                                                                                                                                                                      :> ("teams"
                                                                                                                                                                                                          :> (Capture
                                                                                                                                                                                                                "tid"
                                                                                                                                                                                                                TeamId
                                                                                                                                                                                                              :> ("features"
                                                                                                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (Feature
                                                                                                                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                                          :> Put
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                                                                  EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                                                           :<|> Named
                                                                                                                                                                                  '("ipatch",
                                                                                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                                                                                  (Description
                                                                                                                                                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                                   :> (Summary
                                                                                                                                                                                         "Patch config for enforceFileDownloadLocation"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('MissingPermission
                                                                                                                                                                                                'Nothing)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         TeamFeatureError
                                                                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                                                                             '[]
                                                                                                                                                                                                           :> ("teams"
                                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                                     "tid"
                                                                                                                                                                                                                     TeamId
                                                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                                                       :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                                               :> Patch
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                       EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                                                    :<|> (Named
                                                                                                                                                                            '("iget",
                                                                                                                                                                              LimitedEventFanoutConfig)
                                                                                                                                                                            (Description
                                                                                                                                                                               ""
                                                                                                                                                                             :> (Summary
                                                                                                                                                                                   "Get config for limitedEventFanout"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('MissingPermission
                                                                                                                                                                                          'Nothing)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                       "tid"
                                                                                                                                                                                                       TeamId
                                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                                         :> ("limitedEventFanout"
                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     LimitedEventFanoutConfig))))))))))
                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                  '("iput",
                                                                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                                                                  (Description
                                                                                                                                                                                     ""
                                                                                                                                                                                   :> (Summary
                                                                                                                                                                                         "Put config for limitedEventFanout"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('MissingPermission
                                                                                                                                                                                                'Nothing)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         TeamFeatureError
                                                                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                                                                             '[]
                                                                                                                                                                                                           :> ("teams"
                                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                                     "tid"
                                                                                                                                                                                                                     TeamId
                                                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                                                       :> ("limitedEventFanout"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 (Feature
                                                                                                                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                                                                                                               :> Put
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                       LimitedEventFanoutConfig)))))))))))))
                                                                                                                                                                                :<|> Named
                                                                                                                                                                                       '("ipatch",
                                                                                                                                                                                         LimitedEventFanoutConfig)
                                                                                                                                                                                       (Description
                                                                                                                                                                                          ""
                                                                                                                                                                                        :> (Summary
                                                                                                                                                                                              "Patch config for limitedEventFanout"
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  ('MissingPermission
                                                                                                                                                                                                     'Nothing)
                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                              TeamFeatureError
                                                                                                                                                                                                            :> (CanThrowMany
                                                                                                                                                                                                                  '[]
                                                                                                                                                                                                                :> ("teams"
                                                                                                                                                                                                                    :> (Capture
                                                                                                                                                                                                                          "tid"
                                                                                                                                                                                                                          TeamId
                                                                                                                                                                                                                        :> ("features"
                                                                                                                                                                                                                            :> ("limitedEventFanout"
                                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      (LockableFeaturePatch
                                                                                                                                                                                                                                         LimitedEventFanoutConfig)
                                                                                                                                                                                                                                    :> Patch
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                                                                            LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                                                       :<|> (Named
                                                               '("ilock", FileSharingConfig)
                                                               (Summary "(Un-)lock fileSharing"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("fileSharing"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock",
                                                                       ConferenceCallingConfig)
                                                                     (Summary
                                                                        "(Un-)lock conferenceCalling"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("conferenceCalling"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock",
                                                                             SelfDeletingMessagesConfig)
                                                                           (Summary
                                                                              "(Un-)lock selfDeletingMessages"
                                                                            :> (Description ""
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("selfDeletingMessages"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("ilock",
                                                                                   GuestLinksConfig)
                                                                                 (Summary
                                                                                    "(Un-)lock conversationGuestLinks"
                                                                                  :> (Description ""
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("conversationGuestLinks"
                                                                                                              :> (Capture
                                                                                                                    "lockStatus"
                                                                                                                    LockStatus
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       LockStatusResponse)))))))))
                                                                               :<|> (Named
                                                                                       '("ilock",
                                                                                         SndFactorPasswordChallengeConfig)
                                                                                       (Summary
                                                                                          "(Un-)lock sndFactorPasswordChallenge"
                                                                                        :> (Description
                                                                                              ""
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("sndFactorPasswordChallenge"
                                                                                                                    :> (Capture
                                                                                                                          "lockStatus"
                                                                                                                          LockStatus
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             LockStatusResponse)))))))))
                                                                                     :<|> (Named
                                                                                             '("ilock",
                                                                                               MLSConfig)
                                                                                             (Summary
                                                                                                "(Un-)lock mls"
                                                                                              :> (Description
                                                                                                    ""
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mls"
                                                                                                                          :> (Capture
                                                                                                                                "lockStatus"
                                                                                                                                LockStatus
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   LockStatusResponse)))))))))
                                                                                           :<|> (Named
                                                                                                   '("ilock",
                                                                                                     OutlookCalIntegrationConfig)
                                                                                                   (Summary
                                                                                                      "(Un-)lock outlookCalIntegration"
                                                                                                    :> (Description
                                                                                                          ""
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("outlookCalIntegration"
                                                                                                                                :> (Capture
                                                                                                                                      "lockStatus"
                                                                                                                                      LockStatus
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         LockStatusResponse)))))))))
                                                                                                 :<|> (Named
                                                                                                         '("ilock",
                                                                                                           MlsE2EIdConfig)
                                                                                                         (Summary
                                                                                                            "(Un-)lock mlsE2EId"
                                                                                                          :> (Description
                                                                                                                ""
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("mlsE2EId"
                                                                                                                                      :> (Capture
                                                                                                                                            "lockStatus"
                                                                                                                                            LockStatus
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               LockStatusResponse)))))))))
                                                                                                       :<|> (Named
                                                                                                               '("ilock",
                                                                                                                 MlsMigrationConfig)
                                                                                                               (Summary
                                                                                                                  "(Un-)lock mlsMigration"
                                                                                                                :> (Description
                                                                                                                      ""
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("mlsMigration"
                                                                                                                                            :> (Capture
                                                                                                                                                  "lockStatus"
                                                                                                                                                  LockStatus
                                                                                                                                                :> Put
                                                                                                                                                     '[JSON]
                                                                                                                                                     LockStatusResponse)))))))))
                                                                                                             :<|> (Named
                                                                                                                     '("ilock",
                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                     (Summary
                                                                                                                        "(Un-)lock enforceFileDownloadLocation"
                                                                                                                      :> (Description
                                                                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "lockStatus"
                                                                                                                                                        LockStatus
                                                                                                                                                      :> Put
                                                                                                                                                           '[JSON]
                                                                                                                                                           LockStatusResponse)))))))))
                                                                                                                   :<|> (Named
                                                                                                                           '("igetmulti",
                                                                                                                             SearchVisibilityInboundConfig)
                                                                                                                           (Summary
                                                                                                                              "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                                                            :> ("features-multi-teams"
                                                                                                                                :> ("searchVisibilityInbound"
                                                                                                                                    :> (ReqBody
                                                                                                                                          '[JSON]
                                                                                                                                          TeamFeatureNoConfigMultiRequest
                                                                                                                                        :> Post
                                                                                                                                             '[JSON]
                                                                                                                                             (TeamFeatureNoConfigMultiResponse
                                                                                                                                                SearchVisibilityInboundConfig)))))
                                                                                                                         :<|> Named
                                                                                                                                "feature-configs-internal"
                                                                                                                                (Summary
                                                                                                                                   "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('MissingPermission
                                                                                                                                              'Nothing)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NotATeamMember
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'TeamNotFound
                                                                                                                                                 :> (QueryParam'
                                                                                                                                                       '[Optional,
                                                                                                                                                         Strict,
                                                                                                                                                         Description
                                                                                                                                                           "Optional user id"]
                                                                                                                                                       "user_id"
                                                                                                                                                       UserId
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          AllTeamFeatures))))))))))))))))))
                                                      :<|> (IFederationAPI
                                                            :<|> (IConversationAPI
                                                                  :<|> IEJPDAPI)))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "status"
        ("status" :> MultiVerb 'GET '[JSON] '[RespondEmpty 200 "OK"] ())
      :<|> (Named
              "delete-user"
              (Summary
                 "Remove a user from their teams and conversations and erase their clients"
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (ZLocalUser
                           :> (ZOptConn
                               :> ("user"
                                   :> MultiVerb
                                        'DELETE
                                        '[JSON]
                                        '[RespondEmpty 200 "Remove a user from Galley"]
                                        ()))))))
            :<|> (Named
                    "connect"
                    (Summary "Create a connect conversation (deprecated)"
                     :> (MakesFederatedCall 'Brig "api-version"
                         :> (MakesFederatedCall 'Galley "on-conversation-created"
                             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'InvalidOperation
                                         :> (CanThrow 'NotConnected
                                             :> (CanThrow UnreachableBackends
                                                 :> (ZLocalUser
                                                     :> (ZOptConn
                                                         :> ("conversations"
                                                             :> ("connect"
                                                                 :> (ReqBody '[JSON] Connect
                                                                     :> 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-conversation-clients"
                          (Summary "Get mls conversation client list"
                           :> (CanThrow 'ConvNotFound
                               :> ("group"
                                   :> (Capture "gid" GroupId
                                       :> MultiVerb
                                            'GET
                                            '[JSON]
                                            '[Respond 200 "Clients" ClientList]
                                            ClientList))))
                        :<|> (Named
                                "guard-legalhold-policy-conflicts"
                                ("guard-legalhold-policy-conflicts"
                                 :> (CanThrow 'MissingLegalholdConsent
                                     :> (CanThrow 'MissingLegalholdConsentOldClients
                                         :> (ReqBody '[JSON] GuardLegalholdPolicyConflicts
                                             :> MultiVerb
                                                  'PUT
                                                  '[JSON]
                                                  '[RespondEmpty 200 "Guard Legalhold Policy"]
                                                  ()))))
                              :<|> (("legalhold"
                                     :> ("whitelisted-teams"
                                         :> (Capture "tid" TeamId
                                             :> (Named
                                                   "set-team-legalhold-whitelisted"
                                                   (MultiVerb
                                                      'PUT
                                                      '[JSON]
                                                      '[RespondEmpty
                                                          200 "Team Legalhold Whitelisted"]
                                                      ())
                                                 :<|> (Named
                                                         "unset-team-legalhold-whitelisted"
                                                         (MultiVerb
                                                            'DELETE
                                                            '[JSON]
                                                            '[RespondEmpty
                                                                204 "Team Legalhold un-Whitelisted"]
                                                            ())
                                                       :<|> Named
                                                              "get-team-legalhold-whitelisted"
                                                              (MultiVerb
                                                                 'GET
                                                                 '[JSON]
                                                                 '[RespondEmpty
                                                                     404
                                                                     "Team not Legalhold Whitelisted",
                                                                   RespondEmpty
                                                                     200
                                                                     "Team Legalhold Whitelisted"]
                                                                 Bool))))))
                                    :<|> (("teams"
                                           :> (Capture "tid" TeamId
                                               :> (Named
                                                     "get-team-internal"
                                                     (CanThrow 'TeamNotFound
                                                      :> Get '[JSON] TeamData)
                                                   :<|> (Named
                                                           "create-binding-team"
                                                           (ZUser
                                                            :> (ReqBody '[JSON] BindingNewTeam
                                                                :> MultiVerb
                                                                     'PUT
                                                                     '[JSON]
                                                                     '[WithHeaders
                                                                         '[Header "Location" TeamId]
                                                                         TeamId
                                                                         (RespondEmpty 201 "OK")]
                                                                     TeamId))
                                                         :<|> (Named
                                                                 "delete-binding-team"
                                                                 (CanThrow 'NoBindingTeam
                                                                  :> (CanThrow 'NotAOneMemberTeam
                                                                      :> (CanThrow 'DeleteQueueFull
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> (QueryFlag "force"
                                                                                  :> MultiVerb
                                                                                       'DELETE
                                                                                       '[JSON]
                                                                                       '[RespondEmpty
                                                                                           202 "OK"]
                                                                                       ())))))
                                                               :<|> (Named
                                                                       "get-team-name"
                                                                       ("name"
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> Get
                                                                                 '[JSON] TeamName))
                                                                     :<|> (Named
                                                                             "update-team-status"
                                                                             ("status"
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        'InvalidTeamStatusUpdate
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            TeamStatusUpdate
                                                                                          :> MultiVerb
                                                                                               'PUT
                                                                                               '[JSON]
                                                                                               '[RespondEmpty
                                                                                                   200
                                                                                                   "OK"]
                                                                                               ()))))
                                                                           :<|> (("members"
                                                                                  :> (Named
                                                                                        "unchecked-add-team-member"
                                                                                        (CanThrow
                                                                                           'TooManyTeamMembers
                                                                                         :> (CanThrow
                                                                                               'TooManyTeamMembersOnTeamWithLegalhold
                                                                                             :> (CanThrow
                                                                                                   'TooManyTeamAdmins
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       NewTeamMember
                                                                                                     :> MultiVerb
                                                                                                          'POST
                                                                                                          '[JSON]
                                                                                                          '[RespondEmpty
                                                                                                              200
                                                                                                              "OK"]
                                                                                                          ()))))
                                                                                      :<|> (Named
                                                                                              "unchecked-get-team-members"
                                                                                              (QueryParam'
                                                                                                 '[Strict]
                                                                                                 "maxResults"
                                                                                                 (Range
                                                                                                    1
                                                                                                    HardTruncationLimit
                                                                                                    Int32)
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    TeamMemberList)
                                                                                            :<|> (Named
                                                                                                    "unchecked-get-team-member"
                                                                                                    (Capture
                                                                                                       "uid"
                                                                                                       UserId
                                                                                                     :> (CanThrow
                                                                                                           'TeamMemberNotFound
                                                                                                         :> Get
                                                                                                              '[JSON]
                                                                                                              TeamMember))
                                                                                                  :<|> (Named
                                                                                                          "can-user-join-team"
                                                                                                          ("check"
                                                                                                           :> (CanThrow
                                                                                                                 'TooManyTeamMembersOnTeamWithLegalhold
                                                                                                               :> MultiVerb
                                                                                                                    'GET
                                                                                                                    '[JSON]
                                                                                                                    '[RespondEmpty
                                                                                                                        200
                                                                                                                        "User can join"]
                                                                                                                    ()))
                                                                                                        :<|> Named
                                                                                                               "unchecked-update-team-member"
                                                                                                               (CanThrow
                                                                                                                  'AccessDenied
                                                                                                                :> (CanThrow
                                                                                                                      'InvalidPermissions
                                                                                                                    :> (CanThrow
                                                                                                                          'TeamNotFound
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamMemberNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  'TooManyTeamAdmins
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          ('MissingPermission
                                                                                                                                             'Nothing)
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              NewTeamMember
                                                                                                                                            :> MultiVerb
                                                                                                                                                 'PUT
                                                                                                                                                 '[JSON]
                                                                                                                                                 '[RespondEmpty
                                                                                                                                                     200
                                                                                                                                                     ""]
                                                                                                                                                 ())))))))))))))
                                                                                 :<|> (Named
                                                                                         "user-is-team-owner"
                                                                                         ("is-team-owner"
                                                                                          :> (Capture
                                                                                                "uid"
                                                                                                UserId
                                                                                              :> (CanThrow
                                                                                                    'AccessDenied
                                                                                                  :> (CanThrow
                                                                                                        'TeamMemberNotFound
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> MultiVerb
                                                                                                               'GET
                                                                                                               '[JSON]
                                                                                                               '[RespondEmpty
                                                                                                                   200
                                                                                                                   "User is team owner"]
                                                                                                               ())))))
                                                                                       :<|> ("search-visibility"
                                                                                             :> (Named
                                                                                                   "get-search-visibility-internal"
                                                                                                   (Get
                                                                                                      '[JSON]
                                                                                                      TeamSearchVisibilityView)
                                                                                                 :<|> Named
                                                                                                        "set-search-visibility-internal"
                                                                                                        (CanThrow
                                                                                                           'TeamSearchVisibilityNotEnabled
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           TeamSearchVisibilityView
                                                                                                                         :> MultiVerb
                                                                                                                              'PUT
                                                                                                                              '[JSON]
                                                                                                                              '[RespondEmpty
                                                                                                                                  204
                                                                                                                                  "OK"]
                                                                                                                              ()))))))))))))))))
                                          :<|> ((Named
                                                   "get-team-members"
                                                   (CanThrow 'NonBindingTeam
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("users"
                                                            :> (Capture "uid" UserId
                                                                :> ("team"
                                                                    :> ("members"
                                                                        :> Get
                                                                             '[JSON]
                                                                             TeamMemberList))))))
                                                 :<|> (Named
                                                         "get-team-id"
                                                         (CanThrow 'NonBindingTeam
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("users"
                                                                  :> (Capture "uid" UserId
                                                                      :> ("team"
                                                                          :> Get '[JSON] TeamId)))))
                                                       :<|> (Named
                                                               "test-get-clients"
                                                               ("test"
                                                                :> ("clients"
                                                                    :> (ZUser
                                                                        :> Get '[JSON] [ClientId])))
                                                             :<|> (Named
                                                                     "test-add-client"
                                                                     ("clients"
                                                                      :> (ZUser
                                                                          :> (Capture "cid" ClientId
                                                                              :> MultiVerb
                                                                                   'POST
                                                                                   '[JSON]
                                                                                   '[RespondEmpty
                                                                                       200 "OK"]
                                                                                   ())))
                                                                   :<|> (Named
                                                                           "test-delete-client"
                                                                           ("clients"
                                                                            :> (ZUser
                                                                                :> (Capture
                                                                                      "cid" ClientId
                                                                                    :> MultiVerb
                                                                                         'DELETE
                                                                                         '[JSON]
                                                                                         '[RespondEmpty
                                                                                             200
                                                                                             "OK"]
                                                                                         ())))
                                                                         :<|> (Named
                                                                                 "add-service"
                                                                                 ("services"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        Service
                                                                                      :> MultiVerb
                                                                                           'POST
                                                                                           '[JSON]
                                                                                           '[RespondEmpty
                                                                                               200
                                                                                               "OK"]
                                                                                           ()))
                                                                               :<|> (Named
                                                                                       "delete-service"
                                                                                       ("services"
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              ServiceRef
                                                                                            :> MultiVerb
                                                                                                 'DELETE
                                                                                                 '[JSON]
                                                                                                 '[RespondEmpty
                                                                                                     200
                                                                                                     "OK"]
                                                                                                 ()))
                                                                                     :<|> (Named
                                                                                             "i-add-bot"
                                                                                             (CanThrow
                                                                                                ('ActionDenied
                                                                                                   'AddConversationMember)
                                                                                              :> (CanThrow
                                                                                                    'ConvNotFound
                                                                                                  :> (CanThrow
                                                                                                        'InvalidOperation
                                                                                                      :> (CanThrow
                                                                                                            'TooManyMembers
                                                                                                          :> ("bots"
                                                                                                              :> (ZLocalUser
                                                                                                                  :> (ZConn
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            AddBot
                                                                                                                          :> Post
                                                                                                                               '[JSON]
                                                                                                                               Event))))))))
                                                                                           :<|> (Named
                                                                                                   "delete-bot"
                                                                                                   (CanThrow
                                                                                                      'ConvNotFound
                                                                                                    :> (CanThrow
                                                                                                          ('ActionDenied
                                                                                                             'RemoveConversationMember)
                                                                                                        :> ("bots"
                                                                                                            :> (ZLocalUser
                                                                                                                :> (ZOptConn
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          RemoveBot
                                                                                                                        :> MultiVerb
                                                                                                                             'DELETE
                                                                                                                             '[JSON]
                                                                                                                             (UpdateResponses
                                                                                                                                "Bot not found"
                                                                                                                                "Bot deleted"
                                                                                                                                Event)
                                                                                                                             (UpdateResult
                                                                                                                                Event)))))))
                                                                                                 :<|> (Named
                                                                                                         "put-custom-backend"
                                                                                                         ("custom-backend"
                                                                                                          :> ("by-domain"
                                                                                                              :> (Capture
                                                                                                                    "domain"
                                                                                                                    Domain
                                                                                                                  :> (ReqBody
                                                                                                                        '[JSON]
                                                                                                                        CustomBackend
                                                                                                                      :> MultiVerb
                                                                                                                           'PUT
                                                                                                                           '[JSON]
                                                                                                                           '[RespondEmpty
                                                                                                                               201
                                                                                                                               "OK"]
                                                                                                                           ()))))
                                                                                                       :<|> Named
                                                                                                              "delete-custom-backend"
                                                                                                              ("custom-backend"
                                                                                                               :> ("by-domain"
                                                                                                                   :> (Capture
                                                                                                                         "domain"
                                                                                                                         Domain
                                                                                                                       :> MultiVerb
                                                                                                                            'DELETE
                                                                                                                            '[JSON]
                                                                                                                            '[RespondEmpty
                                                                                                                                200
                                                                                                                                "OK"]
                                                                                                                            ())))))))))))))
                                                :<|> (Named
                                                        "upsert-one2one"
                                                        (Summary
                                                           "Create or Update a connect or one2one conversation."
                                                         :> ("conversations"
                                                             :> ("one2one"
                                                                 :> ("upsert"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           UpsertOne2OneConversationRequest
                                                                         :> MultiVerb
                                                                              'POST
                                                                              '[JSON]
                                                                              '[RespondEmpty
                                                                                  200
                                                                                  "Upsert One2One Policy"]
                                                                              ())))))
                                                      :<|> ((((Named
                                                                 '("iget", LegalholdConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Get config for legalhold"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("legalhold"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          LegalholdConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput", LegalholdConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for legalhold"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[ 'ActionDenied
                                                                                                       'RemoveConversationMember,
                                                                                                     'CannotEnableLegalHoldServiceLargeTeam,
                                                                                                     'LegalHoldNotEnabled,
                                                                                                     'LegalHoldDisableUnimplemented,
                                                                                                     'LegalHoldServiceNotRegistered,
                                                                                                     'UserLegalHoldIllegalOperation,
                                                                                                     'LegalHoldCouldNotBlockConnections]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("legalhold"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         LegalholdConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            LegalholdConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch",
                                                                              LegalholdConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for legalhold"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[ 'ActionDenied
                                                                                                            'RemoveConversationMember,
                                                                                                          'CannotEnableLegalHoldServiceLargeTeam,
                                                                                                          'LegalHoldNotEnabled,
                                                                                                          'LegalHoldDisableUnimplemented,
                                                                                                          'LegalHoldServiceNotRegistered,
                                                                                                          'UserLegalHoldIllegalOperation,
                                                                                                          'LegalHoldCouldNotBlockConnections]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("legalhold"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              LegalholdConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 LegalholdConfig)))))))))))))))
                                                              :<|> ((Named
                                                                       '("iget", SSOConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for sso"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("sso"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SSOConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput", SSOConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for sso"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("sso"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               SSOConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  SSOConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    SSOConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for sso"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("sso"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    SSOConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       SSOConfig)))))))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               SearchVisibilityAvailableConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for searchVisibility"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("searchVisibility"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      SearchVisibilityAvailableConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     SearchVisibilityAvailableConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for searchVisibility"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("searchVisibility"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     SearchVisibilityAvailableConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        SearchVisibilityAvailableConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          SearchVisibilityAvailableConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for searchVisibility"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("searchVisibility"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          SearchVisibilityAvailableConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             SearchVisibilityAvailableConfig)))))))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     SearchVisibilityInboundConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for searchVisibilityInbound"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("searchVisibilityInbound"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            SearchVisibilityInboundConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           SearchVisibilityInboundConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for searchVisibilityInbound"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("searchVisibilityInbound"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           SearchVisibilityInboundConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              SearchVisibilityInboundConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                SearchVisibilityInboundConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for searchVisibilityInbound"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("searchVisibilityInbound"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                SearchVisibilityInboundConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   SearchVisibilityInboundConfig)))))))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           ValidateSAMLEmailsConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for validateSAMLemails"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("validateSAMLemails"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  ValidateSAMLEmailsConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 ValidateSAMLEmailsConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for validateSAMLemails"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("validateSAMLemails"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 ValidateSAMLEmailsConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    ValidateSAMLEmailsConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      ValidateSAMLEmailsConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for validateSAMLemails"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("validateSAMLemails"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      ValidateSAMLEmailsConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         ValidateSAMLEmailsConfig)))))))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 DigitalSignaturesConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for digitalSignatures"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("digitalSignatures"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        DigitalSignaturesConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       DigitalSignaturesConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for digitalSignatures"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("digitalSignatures"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       DigitalSignaturesConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          DigitalSignaturesConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            DigitalSignaturesConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for digitalSignatures"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("digitalSignatures"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            DigitalSignaturesConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               DigitalSignaturesConfig)))))))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       AppLockConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for appLock"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("appLock"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              AppLockConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             AppLockConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for appLock"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("appLock"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             AppLockConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                AppLockConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  AppLockConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for appLock"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("appLock"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  AppLockConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     AppLockConfig)))))))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             FileSharingConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for fileSharing"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("fileSharing"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    FileSharingConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   FileSharingConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for fileSharing"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("fileSharing"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   FileSharingConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      FileSharingConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        FileSharingConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for fileSharing"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("fileSharing"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        FileSharingConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           FileSharingConfig)))))))))))))))
                                                                                                        :<|> (Named
                                                                                                                '("iget",
                                                                                                                  ClassifiedDomainsConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Get config for classifiedDomains"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("classifiedDomains"
                                                                                                                                                 :> Get
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         ClassifiedDomainsConfig))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         ConferenceCallingConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for conferenceCalling"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("conferenceCalling"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                ConferenceCallingConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               ConferenceCallingConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for conferenceCalling"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("conferenceCalling"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               ConferenceCallingConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  ConferenceCallingConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    ConferenceCallingConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for conferenceCalling"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("conferenceCalling"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    ConferenceCallingConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       ConferenceCallingConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               SelfDeletingMessagesConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for selfDeletingMessages"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("selfDeletingMessages"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      SelfDeletingMessagesConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     SelfDeletingMessagesConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for selfDeletingMessages"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("selfDeletingMessages"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     SelfDeletingMessagesConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        SelfDeletingMessagesConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          SelfDeletingMessagesConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for selfDeletingMessages"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("selfDeletingMessages"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          SelfDeletingMessagesConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             SelfDeletingMessagesConfig)))))))))))))))
                                                                                                                          :<|> ((Named
                                                                                                                                   '("iget",
                                                                                                                                     GuestLinksConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for conversationGuestLinks"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("conversationGuestLinks"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            GuestLinksConfig))))))))))
                                                                                                                                 :<|> (Named
                                                                                                                                         '("iput",
                                                                                                                                           GuestLinksConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Put config for conversationGuestLinks"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("conversationGuestLinks"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Feature
                                                                                                                                                                                           GuestLinksConfig)
                                                                                                                                                                                      :> Put
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              GuestLinksConfig)))))))))))))
                                                                                                                                       :<|> Named
                                                                                                                                              '("ipatch",
                                                                                                                                                GuestLinksConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Patch config for conversationGuestLinks"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                GuestLinksConfig)
                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   GuestLinksConfig)))))))))))))))
                                                                                                                                :<|> ((Named
                                                                                                                                         '("iget",
                                                                                                                                           SndFactorPasswordChallengeConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for sndFactorPasswordChallenge"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("sndFactorPasswordChallenge"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                       :<|> (Named
                                                                                                                                               '("iput",
                                                                                                                                                 SndFactorPasswordChallengeConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Put config for sndFactorPasswordChallenge"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                          '[]
                                                                                                                                                                        :> ("teams"
                                                                                                                                                                            :> (Capture
                                                                                                                                                                                  "tid"
                                                                                                                                                                                  TeamId
                                                                                                                                                                                :> ("features"
                                                                                                                                                                                    :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (Feature
                                                                                                                                                                                                 SndFactorPasswordChallengeConfig)
                                                                                                                                                                                            :> Put
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    SndFactorPasswordChallengeConfig)))))))))))))
                                                                                                                                             :<|> Named
                                                                                                                                                    '("ipatch",
                                                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                                                    (Description
                                                                                                                                                       ""
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Patch config for sndFactorPasswordChallenge"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                 :> Patch
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                                                                      :<|> ((Named
                                                                                                                                               '("iget",
                                                                                                                                                 MLSConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Get config for mls"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("mls"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        MLSConfig))))))))))
                                                                                                                                             :<|> (Named
                                                                                                                                                     '("iput",
                                                                                                                                                       MLSConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Put config for mls"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                          :> (CanThrowMany
                                                                                                                                                                                '[]
                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                        "tid"
                                                                                                                                                                                        TeamId
                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                          :> ("mls"
                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (Feature
                                                                                                                                                                                                       MLSConfig)
                                                                                                                                                                                                  :> Put
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          MLSConfig)))))))))))))
                                                                                                                                                   :<|> Named
                                                                                                                                                          '("ipatch",
                                                                                                                                                            MLSConfig)
                                                                                                                                                          (Description
                                                                                                                                                             ""
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Patch config for mls"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('MissingPermission
                                                                                                                                                                        'Nothing)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 TeamFeatureError
                                                                                                                                                                               :> (CanThrowMany
                                                                                                                                                                                     '[]
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> ("mls"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                                                                            MLSConfig)
                                                                                                                                                                                                       :> Patch
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               MLSConfig)))))))))))))))
                                                                                                                                            :<|> ((Named
                                                                                                                                                     '("iget",
                                                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                      :> Get
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                                                                   :<|> (Named
                                                                                                                                                           '("iput",
                                                                                                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                           (Description
                                                                                                                                                              ""
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  TeamFeatureError
                                                                                                                                                                                :> (CanThrowMany
                                                                                                                                                                                      '[]
                                                                                                                                                                                    :> ("teams"
                                                                                                                                                                                        :> (Capture
                                                                                                                                                                                              "tid"
                                                                                                                                                                                              TeamId
                                                                                                                                                                                            :> ("features"
                                                                                                                                                                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (Feature
                                                                                                                                                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                                        :> Put
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                                                                         :<|> Named
                                                                                                                                                                '("ipatch",
                                                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                (Description
                                                                                                                                                                   ""
                                                                                                                                                                 :> (Summary
                                                                                                                                                                       "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('MissingPermission
                                                                                                                                                                              'Nothing)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       TeamFeatureError
                                                                                                                                                                                     :> (CanThrowMany
                                                                                                                                                                                           '[]
                                                                                                                                                                                         :> ("teams"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "tid"
                                                                                                                                                                                                   TeamId
                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                     :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                                             :> Patch
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                                                                  :<|> ((Named
                                                                                                                                                           '("iget",
                                                                                                                                                             OutlookCalIntegrationConfig)
                                                                                                                                                           (Description
                                                                                                                                                              ""
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Get config for outlookCalIntegration"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                :> (Capture
                                                                                                                                                                                      "tid"
                                                                                                                                                                                      TeamId
                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                        :> ("outlookCalIntegration"
                                                                                                                                                                                            :> Get
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    OutlookCalIntegrationConfig))))))))))
                                                                                                                                                         :<|> (Named
                                                                                                                                                                 '("iput",
                                                                                                                                                                   OutlookCalIntegrationConfig)
                                                                                                                                                                 (Description
                                                                                                                                                                    ""
                                                                                                                                                                  :> (Summary
                                                                                                                                                                        "Put config for outlookCalIntegration"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            ('MissingPermission
                                                                                                                                                                               'Nothing)
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        TeamFeatureError
                                                                                                                                                                                      :> (CanThrowMany
                                                                                                                                                                                            '[]
                                                                                                                                                                                          :> ("teams"
                                                                                                                                                                                              :> (Capture
                                                                                                                                                                                                    "tid"
                                                                                                                                                                                                    TeamId
                                                                                                                                                                                                  :> ("features"
                                                                                                                                                                                                      :> ("outlookCalIntegration"
                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (Feature
                                                                                                                                                                                                                   OutlookCalIntegrationConfig)
                                                                                                                                                                                                              :> Put
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                                      OutlookCalIntegrationConfig)))))))))))))
                                                                                                                                                               :<|> Named
                                                                                                                                                                      '("ipatch",
                                                                                                                                                                        OutlookCalIntegrationConfig)
                                                                                                                                                                      (Description
                                                                                                                                                                         ""
                                                                                                                                                                       :> (Summary
                                                                                                                                                                             "Patch config for outlookCalIntegration"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('MissingPermission
                                                                                                                                                                                    'Nothing)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             TeamFeatureError
                                                                                                                                                                                           :> (CanThrowMany
                                                                                                                                                                                                 '[]
                                                                                                                                                                                               :> ("teams"
                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                         "tid"
                                                                                                                                                                                                         TeamId
                                                                                                                                                                                                       :> ("features"
                                                                                                                                                                                                           :> ("outlookCalIntegration"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                                                                        OutlookCalIntegrationConfig)
                                                                                                                                                                                                                   :> Patch
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                           OutlookCalIntegrationConfig)))))))))))))))
                                                                                                                                                        :<|> ((Named
                                                                                                                                                                 '("iget",
                                                                                                                                                                   MlsE2EIdConfig)
                                                                                                                                                                 (Description
                                                                                                                                                                    ""
                                                                                                                                                                  :> (Summary
                                                                                                                                                                        "Get config for mlsE2EId"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            ('MissingPermission
                                                                                                                                                                               'Nothing)
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> ("teams"
                                                                                                                                                                                      :> (Capture
                                                                                                                                                                                            "tid"
                                                                                                                                                                                            TeamId
                                                                                                                                                                                          :> ("features"
                                                                                                                                                                                              :> ("mlsE2EId"
                                                                                                                                                                                                  :> Get
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          MlsE2EIdConfig))))))))))
                                                                                                                                                               :<|> (Named
                                                                                                                                                                       '("iput",
                                                                                                                                                                         MlsE2EIdConfig)
                                                                                                                                                                       (Description
                                                                                                                                                                          ""
                                                                                                                                                                        :> (Summary
                                                                                                                                                                              "Put config for mlsE2EId"
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  ('MissingPermission
                                                                                                                                                                                     'Nothing)
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              TeamFeatureError
                                                                                                                                                                                            :> (CanThrowMany
                                                                                                                                                                                                  '[]
                                                                                                                                                                                                :> ("teams"
                                                                                                                                                                                                    :> (Capture
                                                                                                                                                                                                          "tid"
                                                                                                                                                                                                          TeamId
                                                                                                                                                                                                        :> ("features"
                                                                                                                                                                                                            :> ("mlsE2EId"
                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (Feature
                                                                                                                                                                                                                         MlsE2EIdConfig)
                                                                                                                                                                                                                    :> Put
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                                                            MlsE2EIdConfig)))))))))))))
                                                                                                                                                                     :<|> Named
                                                                                                                                                                            '("ipatch",
                                                                                                                                                                              MlsE2EIdConfig)
                                                                                                                                                                            (Description
                                                                                                                                                                               ""
                                                                                                                                                                             :> (Summary
                                                                                                                                                                                   "Patch config for mlsE2EId"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('MissingPermission
                                                                                                                                                                                          'Nothing)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   TeamFeatureError
                                                                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                                                                       '[]
                                                                                                                                                                                                     :> ("teams"
                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                               "tid"
                                                                                                                                                                                                               TeamId
                                                                                                                                                                                                             :> ("features"
                                                                                                                                                                                                                 :> ("mlsE2EId"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                                                                              MlsE2EIdConfig)
                                                                                                                                                                                                                         :> Patch
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                 MlsE2EIdConfig)))))))))))))))
                                                                                                                                                              :<|> ((Named
                                                                                                                                                                       '("iget",
                                                                                                                                                                         MlsMigrationConfig)
                                                                                                                                                                       (Description
                                                                                                                                                                          ""
                                                                                                                                                                        :> (Summary
                                                                                                                                                                              "Get config for mlsMigration"
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  ('MissingPermission
                                                                                                                                                                                     'Nothing)
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                        :> ("teams"
                                                                                                                                                                                            :> (Capture
                                                                                                                                                                                                  "tid"
                                                                                                                                                                                                  TeamId
                                                                                                                                                                                                :> ("features"
                                                                                                                                                                                                    :> ("mlsMigration"
                                                                                                                                                                                                        :> Get
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                MlsMigrationConfig))))))))))
                                                                                                                                                                     :<|> (Named
                                                                                                                                                                             '("iput",
                                                                                                                                                                               MlsMigrationConfig)
                                                                                                                                                                             (Description
                                                                                                                                                                                ""
                                                                                                                                                                              :> (Summary
                                                                                                                                                                                    "Put config for mlsMigration"
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        ('MissingPermission
                                                                                                                                                                                           'Nothing)
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    TeamFeatureError
                                                                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                                                                        '[]
                                                                                                                                                                                                      :> ("teams"
                                                                                                                                                                                                          :> (Capture
                                                                                                                                                                                                                "tid"
                                                                                                                                                                                                                TeamId
                                                                                                                                                                                                              :> ("features"
                                                                                                                                                                                                                  :> ("mlsMigration"
                                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (Feature
                                                                                                                                                                                                                               MlsMigrationConfig)
                                                                                                                                                                                                                          :> Put
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                                                                  MlsMigrationConfig)))))))))))))
                                                                                                                                                                           :<|> Named
                                                                                                                                                                                  '("ipatch",
                                                                                                                                                                                    MlsMigrationConfig)
                                                                                                                                                                                  (Description
                                                                                                                                                                                     ""
                                                                                                                                                                                   :> (Summary
                                                                                                                                                                                         "Patch config for mlsMigration"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('MissingPermission
                                                                                                                                                                                                'Nothing)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         TeamFeatureError
                                                                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                                                                             '[]
                                                                                                                                                                                                           :> ("teams"
                                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                                     "tid"
                                                                                                                                                                                                                     TeamId
                                                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                                                       :> ("mlsMigration"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                                                                    MlsMigrationConfig)
                                                                                                                                                                                                                               :> Patch
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                       MlsMigrationConfig)))))))))))))))
                                                                                                                                                                    :<|> ((Named
                                                                                                                                                                             '("iget",
                                                                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                                                                             (Description
                                                                                                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                              :> (Summary
                                                                                                                                                                                    "Get config for enforceFileDownloadLocation"
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        ('MissingPermission
                                                                                                                                                                                           'Nothing)
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                                        "tid"
                                                                                                                                                                                                        TeamId
                                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                              :> Get
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                                      EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                                                           :<|> (Named
                                                                                                                                                                                   '("iput",
                                                                                                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                                                                                                   (Description
                                                                                                                                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                                    :> (Summary
                                                                                                                                                                                          "Put config for enforceFileDownloadLocation"
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              ('MissingPermission
                                                                                                                                                                                                 'Nothing)
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                          TeamFeatureError
                                                                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                                                                              '[]
                                                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                                                :> (Capture
                                                                                                                                                                                                                      "tid"
                                                                                                                                                                                                                      TeamId
                                                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                                                        :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (Feature
                                                                                                                                                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                                                :> Put
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                                                                        EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                                                                 :<|> Named
                                                                                                                                                                                        '("ipatch",
                                                                                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                                                                                        (Description
                                                                                                                                                                                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                                         :> (Summary
                                                                                                                                                                                               "Patch config for enforceFileDownloadLocation"
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('MissingPermission
                                                                                                                                                                                                      'Nothing)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               TeamFeatureError
                                                                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                                                                   '[]
                                                                                                                                                                                                                 :> ("teams"
                                                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                                                           "tid"
                                                                                                                                                                                                                           TeamId
                                                                                                                                                                                                                         :> ("features"
                                                                                                                                                                                                                             :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                                                     :> Patch
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                                                             EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                  '("iget",
                                                                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                                                                  (Description
                                                                                                                                                                                     ""
                                                                                                                                                                                   :> (Summary
                                                                                                                                                                                         "Get config for limitedEventFanout"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('MissingPermission
                                                                                                                                                                                                'Nothing)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                                             "tid"
                                                                                                                                                                                                             TeamId
                                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                                               :> ("limitedEventFanout"
                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                           LimitedEventFanoutConfig))))))))))
                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                        '("iput",
                                                                                                                                                                                          LimitedEventFanoutConfig)
                                                                                                                                                                                        (Description
                                                                                                                                                                                           ""
                                                                                                                                                                                         :> (Summary
                                                                                                                                                                                               "Put config for limitedEventFanout"
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('MissingPermission
                                                                                                                                                                                                      'Nothing)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               TeamFeatureError
                                                                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                                                                   '[]
                                                                                                                                                                                                                 :> ("teams"
                                                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                                                           "tid"
                                                                                                                                                                                                                           TeamId
                                                                                                                                                                                                                         :> ("features"
                                                                                                                                                                                                                             :> ("limitedEventFanout"
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       (Feature
                                                                                                                                                                                                                                          LimitedEventFanoutConfig)
                                                                                                                                                                                                                                     :> Put
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                                                             LimitedEventFanoutConfig)))))))))))))
                                                                                                                                                                                      :<|> Named
                                                                                                                                                                                             '("ipatch",
                                                                                                                                                                                               LimitedEventFanoutConfig)
                                                                                                                                                                                             (Description
                                                                                                                                                                                                ""
                                                                                                                                                                                              :> (Summary
                                                                                                                                                                                                    "Patch config for limitedEventFanout"
                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                        ('MissingPermission
                                                                                                                                                                                                           'Nothing)
                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                    TeamFeatureError
                                                                                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                                                                                        '[]
                                                                                                                                                                                                                      :> ("teams"
                                                                                                                                                                                                                          :> (Capture
                                                                                                                                                                                                                                "tid"
                                                                                                                                                                                                                                TeamId
                                                                                                                                                                                                                              :> ("features"
                                                                                                                                                                                                                                  :> ("limitedEventFanout"
                                                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            (LockableFeaturePatch
                                                                                                                                                                                                                                               LimitedEventFanoutConfig)
                                                                                                                                                                                                                                          :> Patch
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                                                                                  LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                                                             :<|> (Named
                                                                     '("ilock", FileSharingConfig)
                                                                     (Summary
                                                                        "(Un-)lock fileSharing"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("fileSharing"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock",
                                                                             ConferenceCallingConfig)
                                                                           (Summary
                                                                              "(Un-)lock conferenceCalling"
                                                                            :> (Description ""
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("conferenceCalling"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("ilock",
                                                                                   SelfDeletingMessagesConfig)
                                                                                 (Summary
                                                                                    "(Un-)lock selfDeletingMessages"
                                                                                  :> (Description ""
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("selfDeletingMessages"
                                                                                                              :> (Capture
                                                                                                                    "lockStatus"
                                                                                                                    LockStatus
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       LockStatusResponse)))))))))
                                                                               :<|> (Named
                                                                                       '("ilock",
                                                                                         GuestLinksConfig)
                                                                                       (Summary
                                                                                          "(Un-)lock conversationGuestLinks"
                                                                                        :> (Description
                                                                                              ""
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("conversationGuestLinks"
                                                                                                                    :> (Capture
                                                                                                                          "lockStatus"
                                                                                                                          LockStatus
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             LockStatusResponse)))))))))
                                                                                     :<|> (Named
                                                                                             '("ilock",
                                                                                               SndFactorPasswordChallengeConfig)
                                                                                             (Summary
                                                                                                "(Un-)lock sndFactorPasswordChallenge"
                                                                                              :> (Description
                                                                                                    ""
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("sndFactorPasswordChallenge"
                                                                                                                          :> (Capture
                                                                                                                                "lockStatus"
                                                                                                                                LockStatus
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   LockStatusResponse)))))))))
                                                                                           :<|> (Named
                                                                                                   '("ilock",
                                                                                                     MLSConfig)
                                                                                                   (Summary
                                                                                                      "(Un-)lock mls"
                                                                                                    :> (Description
                                                                                                          ""
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mls"
                                                                                                                                :> (Capture
                                                                                                                                      "lockStatus"
                                                                                                                                      LockStatus
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         LockStatusResponse)))))))))
                                                                                                 :<|> (Named
                                                                                                         '("ilock",
                                                                                                           OutlookCalIntegrationConfig)
                                                                                                         (Summary
                                                                                                            "(Un-)lock outlookCalIntegration"
                                                                                                          :> (Description
                                                                                                                ""
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("outlookCalIntegration"
                                                                                                                                      :> (Capture
                                                                                                                                            "lockStatus"
                                                                                                                                            LockStatus
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               LockStatusResponse)))))))))
                                                                                                       :<|> (Named
                                                                                                               '("ilock",
                                                                                                                 MlsE2EIdConfig)
                                                                                                               (Summary
                                                                                                                  "(Un-)lock mlsE2EId"
                                                                                                                :> (Description
                                                                                                                      ""
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("mlsE2EId"
                                                                                                                                            :> (Capture
                                                                                                                                                  "lockStatus"
                                                                                                                                                  LockStatus
                                                                                                                                                :> Put
                                                                                                                                                     '[JSON]
                                                                                                                                                     LockStatusResponse)))))))))
                                                                                                             :<|> (Named
                                                                                                                     '("ilock",
                                                                                                                       MlsMigrationConfig)
                                                                                                                     (Summary
                                                                                                                        "(Un-)lock mlsMigration"
                                                                                                                      :> (Description
                                                                                                                            ""
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("mlsMigration"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "lockStatus"
                                                                                                                                                        LockStatus
                                                                                                                                                      :> Put
                                                                                                                                                           '[JSON]
                                                                                                                                                           LockStatusResponse)))))))))
                                                                                                                   :<|> (Named
                                                                                                                           '("ilock",
                                                                                                                             EnforceFileDownloadLocationConfig)
                                                                                                                           (Summary
                                                                                                                              "(Un-)lock enforceFileDownloadLocation"
                                                                                                                            :> (Description
                                                                                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "lockStatus"
                                                                                                                                                              LockStatus
                                                                                                                                                            :> Put
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 LockStatusResponse)))))))))
                                                                                                                         :<|> (Named
                                                                                                                                 '("igetmulti",
                                                                                                                                   SearchVisibilityInboundConfig)
                                                                                                                                 (Summary
                                                                                                                                    "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                                                                  :> ("features-multi-teams"
                                                                                                                                      :> ("searchVisibilityInbound"
                                                                                                                                          :> (ReqBody
                                                                                                                                                '[JSON]
                                                                                                                                                TeamFeatureNoConfigMultiRequest
                                                                                                                                              :> Post
                                                                                                                                                   '[JSON]
                                                                                                                                                   (TeamFeatureNoConfigMultiResponse
                                                                                                                                                      SearchVisibilityInboundConfig)))))
                                                                                                                               :<|> Named
                                                                                                                                      "feature-configs-internal"
                                                                                                                                      (Summary
                                                                                                                                         "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('MissingPermission
                                                                                                                                                    'Nothing)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'NotATeamMember
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'TeamNotFound
                                                                                                                                                       :> (QueryParam'
                                                                                                                                                             '[Optional,
                                                                                                                                                               Strict,
                                                                                                                                                               Description
                                                                                                                                                                 "Optional user id"]
                                                                                                                                                             "user_id"
                                                                                                                                                             UserId
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                AllTeamFeatures))))))))))))))))))
                                                            :<|> (IFederationAPI
                                                                  :<|> (IConversationAPI
                                                                        :<|> IEJPDAPI))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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-user" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   () :: Constraint)) =>
 QualifiedWithTag 'QLocal UserId
 -> Maybe ConnId
 -> 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]
      ())
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> 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]
     ()
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> Maybe ConnId
 -> 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]
      ())
-> QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> 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]
     ()
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> 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]
     ()
forall p1 p2 (r :: EffectRow).
(p1 ~ CassandraPaging, p2 ~ InternalPaging,
 Member BackendNotificationQueueAccess r, Member ClientStore r,
 Member ConversationStore r, Member (Error DynError) r,
 Member (Error FederationError) r, Member (Error InternalError) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input Env) r, Member (Input Opts) r,
 Member (Input UTCTime) r, Member (ListItems p1 ConvId) r,
 Member (ListItems p1 (Remote ConvId)) r,
 Member (ListItems p2 TeamId) r, Member MemberStore r,
 Member ProposalStore r, Member (Logger (Msg -> Msg)) r,
 Member Random r, Member SubConversationStore r,
 Member TeamFeatureStore r, Member TeamStore r) =>
QualifiedWithTag 'QLocal UserId -> Maybe ConnId -> Sem r ()
rmUser))
      API
  (Named
     "delete-user"
     (Summary
        "Remove a user from their teams and conversations and erase their clients"
      :> (MakesFederatedCall 'Galley "on-conversation-updated"
          :> (MakesFederatedCall 'Galley "on-mls-message-sent"
              :> (ZLocalUser
                  :> (ZOptConn
                      :> ("user"
                          :> MultiVerb
                               'DELETE
                               '[JSON]
                               '[RespondEmpty 200 "Remove a user from Galley"]
                               ())))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "connect"
        (Summary "Create a connect conversation (deprecated)"
         :> (MakesFederatedCall 'Brig "api-version"
             :> (MakesFederatedCall 'Galley "on-conversation-created"
                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'InvalidOperation
                             :> (CanThrow 'NotConnected
                                 :> (CanThrow UnreachableBackends
                                     :> (ZLocalUser
                                         :> (ZOptConn
                                             :> ("conversations"
                                                 :> ("connect"
                                                     :> (ReqBody '[JSON] Connect
                                                         :> 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-conversation-clients"
              (Summary "Get mls conversation client list"
               :> (CanThrow 'ConvNotFound
                   :> ("group"
                       :> (Capture "gid" GroupId
                           :> MultiVerb
                                'GET '[JSON] '[Respond 200 "Clients" ClientList] ClientList))))
            :<|> (Named
                    "guard-legalhold-policy-conflicts"
                    ("guard-legalhold-policy-conflicts"
                     :> (CanThrow 'MissingLegalholdConsent
                         :> (CanThrow 'MissingLegalholdConsentOldClients
                             :> (ReqBody '[JSON] GuardLegalholdPolicyConflicts
                                 :> MultiVerb
                                      'PUT
                                      '[JSON]
                                      '[RespondEmpty 200 "Guard Legalhold Policy"]
                                      ()))))
                  :<|> (("legalhold"
                         :> ("whitelisted-teams"
                             :> (Capture "tid" TeamId
                                 :> (Named
                                       "set-team-legalhold-whitelisted"
                                       (MultiVerb
                                          'PUT
                                          '[JSON]
                                          '[RespondEmpty 200 "Team Legalhold Whitelisted"]
                                          ())
                                     :<|> (Named
                                             "unset-team-legalhold-whitelisted"
                                             (MultiVerb
                                                'DELETE
                                                '[JSON]
                                                '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
                                                ())
                                           :<|> Named
                                                  "get-team-legalhold-whitelisted"
                                                  (MultiVerb
                                                     'GET
                                                     '[JSON]
                                                     '[RespondEmpty
                                                         404 "Team not Legalhold Whitelisted",
                                                       RespondEmpty
                                                         200 "Team Legalhold Whitelisted"]
                                                     Bool))))))
                        :<|> (("teams"
                               :> (Capture "tid" TeamId
                                   :> (Named
                                         "get-team-internal"
                                         (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
                                       :<|> (Named
                                               "create-binding-team"
                                               (ZUser
                                                :> (ReqBody '[JSON] BindingNewTeam
                                                    :> MultiVerb
                                                         'PUT
                                                         '[JSON]
                                                         '[WithHeaders
                                                             '[Header "Location" TeamId]
                                                             TeamId
                                                             (RespondEmpty 201 "OK")]
                                                         TeamId))
                                             :<|> (Named
                                                     "delete-binding-team"
                                                     (CanThrow 'NoBindingTeam
                                                      :> (CanThrow 'NotAOneMemberTeam
                                                          :> (CanThrow 'DeleteQueueFull
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> (QueryFlag "force"
                                                                      :> MultiVerb
                                                                           'DELETE
                                                                           '[JSON]
                                                                           '[RespondEmpty 202 "OK"]
                                                                           ())))))
                                                   :<|> (Named
                                                           "get-team-name"
                                                           ("name"
                                                            :> (CanThrow 'TeamNotFound
                                                                :> Get '[JSON] TeamName))
                                                         :<|> (Named
                                                                 "update-team-status"
                                                                 ("status"
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow
                                                                            'InvalidTeamStatusUpdate
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                TeamStatusUpdate
                                                                              :> MultiVerb
                                                                                   'PUT
                                                                                   '[JSON]
                                                                                   '[RespondEmpty
                                                                                       200 "OK"]
                                                                                   ()))))
                                                               :<|> (("members"
                                                                      :> (Named
                                                                            "unchecked-add-team-member"
                                                                            (CanThrow
                                                                               'TooManyTeamMembers
                                                                             :> (CanThrow
                                                                                   'TooManyTeamMembersOnTeamWithLegalhold
                                                                                 :> (CanThrow
                                                                                       'TooManyTeamAdmins
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           NewTeamMember
                                                                                         :> MultiVerb
                                                                                              'POST
                                                                                              '[JSON]
                                                                                              '[RespondEmpty
                                                                                                  200
                                                                                                  "OK"]
                                                                                              ()))))
                                                                          :<|> (Named
                                                                                  "unchecked-get-team-members"
                                                                                  (QueryParam'
                                                                                     '[Strict]
                                                                                     "maxResults"
                                                                                     (Range
                                                                                        1
                                                                                        HardTruncationLimit
                                                                                        Int32)
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        TeamMemberList)
                                                                                :<|> (Named
                                                                                        "unchecked-get-team-member"
                                                                                        (Capture
                                                                                           "uid"
                                                                                           UserId
                                                                                         :> (CanThrow
                                                                                               'TeamMemberNotFound
                                                                                             :> Get
                                                                                                  '[JSON]
                                                                                                  TeamMember))
                                                                                      :<|> (Named
                                                                                              "can-user-join-team"
                                                                                              ("check"
                                                                                               :> (CanThrow
                                                                                                     'TooManyTeamMembersOnTeamWithLegalhold
                                                                                                   :> MultiVerb
                                                                                                        'GET
                                                                                                        '[JSON]
                                                                                                        '[RespondEmpty
                                                                                                            200
                                                                                                            "User can join"]
                                                                                                        ()))
                                                                                            :<|> Named
                                                                                                   "unchecked-update-team-member"
                                                                                                   (CanThrow
                                                                                                      'AccessDenied
                                                                                                    :> (CanThrow
                                                                                                          'InvalidPermissions
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> (CanThrow
                                                                                                                  'TeamMemberNotFound
                                                                                                                :> (CanThrow
                                                                                                                      'TooManyTeamAdmins
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              ('MissingPermission
                                                                                                                                 'Nothing)
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  NewTeamMember
                                                                                                                                :> MultiVerb
                                                                                                                                     'PUT
                                                                                                                                     '[JSON]
                                                                                                                                     '[RespondEmpty
                                                                                                                                         200
                                                                                                                                         ""]
                                                                                                                                     ())))))))))))))
                                                                     :<|> (Named
                                                                             "user-is-team-owner"
                                                                             ("is-team-owner"
                                                                              :> (Capture
                                                                                    "uid" UserId
                                                                                  :> (CanThrow
                                                                                        'AccessDenied
                                                                                      :> (CanThrow
                                                                                            'TeamMemberNotFound
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> MultiVerb
                                                                                                   'GET
                                                                                                   '[JSON]
                                                                                                   '[RespondEmpty
                                                                                                       200
                                                                                                       "User is team owner"]
                                                                                                   ())))))
                                                                           :<|> ("search-visibility"
                                                                                 :> (Named
                                                                                       "get-search-visibility-internal"
                                                                                       (Get
                                                                                          '[JSON]
                                                                                          TeamSearchVisibilityView)
                                                                                     :<|> Named
                                                                                            "set-search-visibility-internal"
                                                                                            (CanThrow
                                                                                               'TeamSearchVisibilityNotEnabled
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               TeamSearchVisibilityView
                                                                                                             :> MultiVerb
                                                                                                                  'PUT
                                                                                                                  '[JSON]
                                                                                                                  '[RespondEmpty
                                                                                                                      204
                                                                                                                      "OK"]
                                                                                                                  ()))))))))))))))))
                              :<|> ((Named
                                       "get-team-members"
                                       (CanThrow 'NonBindingTeam
                                        :> (CanThrow 'TeamNotFound
                                            :> ("users"
                                                :> (Capture "uid" UserId
                                                    :> ("team"
                                                        :> ("members"
                                                            :> Get '[JSON] TeamMemberList))))))
                                     :<|> (Named
                                             "get-team-id"
                                             (CanThrow 'NonBindingTeam
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("users"
                                                      :> (Capture "uid" UserId
                                                          :> ("team" :> Get '[JSON] TeamId)))))
                                           :<|> (Named
                                                   "test-get-clients"
                                                   ("test"
                                                    :> ("clients"
                                                        :> (ZUser :> Get '[JSON] [ClientId])))
                                                 :<|> (Named
                                                         "test-add-client"
                                                         ("clients"
                                                          :> (ZUser
                                                              :> (Capture "cid" ClientId
                                                                  :> MultiVerb
                                                                       'POST
                                                                       '[JSON]
                                                                       '[RespondEmpty 200 "OK"]
                                                                       ())))
                                                       :<|> (Named
                                                               "test-delete-client"
                                                               ("clients"
                                                                :> (ZUser
                                                                    :> (Capture "cid" ClientId
                                                                        :> MultiVerb
                                                                             'DELETE
                                                                             '[JSON]
                                                                             '[RespondEmpty
                                                                                 200 "OK"]
                                                                             ())))
                                                             :<|> (Named
                                                                     "add-service"
                                                                     ("services"
                                                                      :> (ReqBody '[JSON] Service
                                                                          :> MultiVerb
                                                                               'POST
                                                                               '[JSON]
                                                                               '[RespondEmpty
                                                                                   200 "OK"]
                                                                               ()))
                                                                   :<|> (Named
                                                                           "delete-service"
                                                                           ("services"
                                                                            :> (ReqBody
                                                                                  '[JSON] ServiceRef
                                                                                :> MultiVerb
                                                                                     'DELETE
                                                                                     '[JSON]
                                                                                     '[RespondEmpty
                                                                                         200 "OK"]
                                                                                     ()))
                                                                         :<|> (Named
                                                                                 "i-add-bot"
                                                                                 (CanThrow
                                                                                    ('ActionDenied
                                                                                       'AddConversationMember)
                                                                                  :> (CanThrow
                                                                                        'ConvNotFound
                                                                                      :> (CanThrow
                                                                                            'InvalidOperation
                                                                                          :> (CanThrow
                                                                                                'TooManyMembers
                                                                                              :> ("bots"
                                                                                                  :> (ZLocalUser
                                                                                                      :> (ZConn
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                AddBot
                                                                                                              :> Post
                                                                                                                   '[JSON]
                                                                                                                   Event))))))))
                                                                               :<|> (Named
                                                                                       "delete-bot"
                                                                                       (CanThrow
                                                                                          'ConvNotFound
                                                                                        :> (CanThrow
                                                                                              ('ActionDenied
                                                                                                 'RemoveConversationMember)
                                                                                            :> ("bots"
                                                                                                :> (ZLocalUser
                                                                                                    :> (ZOptConn
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              RemoveBot
                                                                                                            :> MultiVerb
                                                                                                                 'DELETE
                                                                                                                 '[JSON]
                                                                                                                 (UpdateResponses
                                                                                                                    "Bot not found"
                                                                                                                    "Bot deleted"
                                                                                                                    Event)
                                                                                                                 (UpdateResult
                                                                                                                    Event)))))))
                                                                                     :<|> (Named
                                                                                             "put-custom-backend"
                                                                                             ("custom-backend"
                                                                                              :> ("by-domain"
                                                                                                  :> (Capture
                                                                                                        "domain"
                                                                                                        Domain
                                                                                                      :> (ReqBody
                                                                                                            '[JSON]
                                                                                                            CustomBackend
                                                                                                          :> MultiVerb
                                                                                                               'PUT
                                                                                                               '[JSON]
                                                                                                               '[RespondEmpty
                                                                                                                   201
                                                                                                                   "OK"]
                                                                                                               ()))))
                                                                                           :<|> Named
                                                                                                  "delete-custom-backend"
                                                                                                  ("custom-backend"
                                                                                                   :> ("by-domain"
                                                                                                       :> (Capture
                                                                                                             "domain"
                                                                                                             Domain
                                                                                                           :> MultiVerb
                                                                                                                'DELETE
                                                                                                                '[JSON]
                                                                                                                '[RespondEmpty
                                                                                                                    200
                                                                                                                    "OK"]
                                                                                                                ())))))))))))))
                                    :<|> (Named
                                            "upsert-one2one"
                                            (Summary
                                               "Create or Update a connect or one2one conversation."
                                             :> ("conversations"
                                                 :> ("one2one"
                                                     :> ("upsert"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               UpsertOne2OneConversationRequest
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[RespondEmpty
                                                                      200 "Upsert One2One Policy"]
                                                                  ())))))
                                          :<|> ((((Named
                                                     '("iget", LegalholdConfig)
                                                     (Description ""
                                                      :> (Summary "Get config for legalhold"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("legalhold"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              LegalholdConfig))))))))))
                                                   :<|> (Named
                                                           '("iput", LegalholdConfig)
                                                           (Description ""
                                                            :> (Summary "Put config for legalhold"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany
                                                                                      '[ 'ActionDenied
                                                                                           'RemoveConversationMember,
                                                                                         'CannotEnableLegalHoldServiceLargeTeam,
                                                                                         'LegalHoldNotEnabled,
                                                                                         'LegalHoldDisableUnimplemented,
                                                                                         'LegalHoldServiceNotRegistered,
                                                                                         'UserLegalHoldIllegalOperation,
                                                                                         'LegalHoldCouldNotBlockConnections]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("legalhold"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             LegalholdConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                LegalholdConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch", LegalholdConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Patch config for legalhold"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[ 'ActionDenied
                                                                                                'RemoveConversationMember,
                                                                                              'CannotEnableLegalHoldServiceLargeTeam,
                                                                                              'LegalHoldNotEnabled,
                                                                                              'LegalHoldDisableUnimplemented,
                                                                                              'LegalHoldServiceNotRegistered,
                                                                                              'UserLegalHoldIllegalOperation,
                                                                                              'LegalHoldCouldNotBlockConnections]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("legalhold"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  LegalholdConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     LegalholdConfig)))))))))))))))
                                                  :<|> ((Named
                                                           '("iget", SSOConfig)
                                                           (Description ""
                                                            :> (Summary "Get config for sso"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("sso"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    SSOConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput", SSOConfig)
                                                                 (Description ""
                                                                  :> (Summary "Put config for sso"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("sso"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   SSOConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      SSOConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch", SSOConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for sso"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("sso"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        SSOConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           SSOConfig)))))))))))))))
                                                        :<|> ((Named
                                                                 '("iget",
                                                                   SearchVisibilityAvailableConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Get config for searchVisibility"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("searchVisibility"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          SearchVisibilityAvailableConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput",
                                                                         SearchVisibilityAvailableConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for searchVisibility"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("searchVisibility"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         SearchVisibilityAvailableConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            SearchVisibilityAvailableConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch",
                                                                              SearchVisibilityAvailableConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for searchVisibility"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("searchVisibility"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              SearchVisibilityAvailableConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 SearchVisibilityAvailableConfig)))))))))))))))
                                                              :<|> ((Named
                                                                       '("iget",
                                                                         SearchVisibilityInboundConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for searchVisibilityInbound"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("searchVisibilityInbound"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SearchVisibilityInboundConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               SearchVisibilityInboundConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for searchVisibilityInbound"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("searchVisibilityInbound"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               SearchVisibilityInboundConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  SearchVisibilityInboundConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    SearchVisibilityInboundConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for searchVisibilityInbound"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("searchVisibilityInbound"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    SearchVisibilityInboundConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       SearchVisibilityInboundConfig)))))))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               ValidateSAMLEmailsConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for validateSAMLemails"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("validateSAMLemails"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      ValidateSAMLEmailsConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     ValidateSAMLEmailsConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for validateSAMLemails"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("validateSAMLemails"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     ValidateSAMLEmailsConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        ValidateSAMLEmailsConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          ValidateSAMLEmailsConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for validateSAMLemails"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("validateSAMLemails"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          ValidateSAMLEmailsConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             ValidateSAMLEmailsConfig)))))))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     DigitalSignaturesConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for digitalSignatures"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("digitalSignatures"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            DigitalSignaturesConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           DigitalSignaturesConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for digitalSignatures"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("digitalSignatures"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           DigitalSignaturesConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              DigitalSignaturesConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                DigitalSignaturesConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for digitalSignatures"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("digitalSignatures"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                DigitalSignaturesConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   DigitalSignaturesConfig)))))))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           AppLockConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for appLock"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("appLock"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  AppLockConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 AppLockConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for appLock"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("appLock"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 AppLockConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    AppLockConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      AppLockConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for appLock"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("appLock"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      AppLockConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         AppLockConfig)))))))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 FileSharingConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for fileSharing"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("fileSharing"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        FileSharingConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       FileSharingConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for fileSharing"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("fileSharing"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       FileSharingConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          FileSharingConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            FileSharingConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for fileSharing"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("fileSharing"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            FileSharingConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               FileSharingConfig)))))))))))))))
                                                                                            :<|> (Named
                                                                                                    '("iget",
                                                                                                      ClassifiedDomainsConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Get config for classifiedDomains"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("classifiedDomains"
                                                                                                                                     :> Get
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             ClassifiedDomainsConfig))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             ConferenceCallingConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for conferenceCalling"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("conferenceCalling"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    ConferenceCallingConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   ConferenceCallingConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for conferenceCalling"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("conferenceCalling"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   ConferenceCallingConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      ConferenceCallingConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        ConferenceCallingConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for conferenceCalling"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("conferenceCalling"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        ConferenceCallingConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           ConferenceCallingConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   SelfDeletingMessagesConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for selfDeletingMessages"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("selfDeletingMessages"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          SelfDeletingMessagesConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         SelfDeletingMessagesConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for selfDeletingMessages"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("selfDeletingMessages"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         SelfDeletingMessagesConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            SelfDeletingMessagesConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              SelfDeletingMessagesConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for selfDeletingMessages"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("selfDeletingMessages"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              SelfDeletingMessagesConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 SelfDeletingMessagesConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         GuestLinksConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for conversationGuestLinks"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("conversationGuestLinks"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                GuestLinksConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               GuestLinksConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for conversationGuestLinks"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("conversationGuestLinks"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               GuestLinksConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  GuestLinksConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    GuestLinksConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for conversationGuestLinks"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    GuestLinksConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       GuestLinksConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               SndFactorPasswordChallengeConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for sndFactorPasswordChallenge"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("sndFactorPasswordChallenge"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      SndFactorPasswordChallengeConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     SndFactorPasswordChallengeConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for sndFactorPasswordChallenge"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("sndFactorPasswordChallenge"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     SndFactorPasswordChallengeConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        SndFactorPasswordChallengeConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          SndFactorPasswordChallengeConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for sndFactorPasswordChallenge"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          SndFactorPasswordChallengeConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                                                          :<|> ((Named
                                                                                                                                   '("iget",
                                                                                                                                     MLSConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for mls"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("mls"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MLSConfig))))))))))
                                                                                                                                 :<|> (Named
                                                                                                                                         '("iput",
                                                                                                                                           MLSConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Put config for mls"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("mls"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Feature
                                                                                                                                                                                           MLSConfig)
                                                                                                                                                                                      :> Put
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              MLSConfig)))))))))))))
                                                                                                                                       :<|> Named
                                                                                                                                              '("ipatch",
                                                                                                                                                MLSConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Patch config for mls"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("mls"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                MLSConfig)
                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   MLSConfig)))))))))))))))
                                                                                                                                :<|> ((Named
                                                                                                                                         '("iget",
                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                                                       :<|> (Named
                                                                                                                                               '("iput",
                                                                                                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                          '[]
                                                                                                                                                                        :> ("teams"
                                                                                                                                                                            :> (Capture
                                                                                                                                                                                  "tid"
                                                                                                                                                                                  TeamId
                                                                                                                                                                                :> ("features"
                                                                                                                                                                                    :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (Feature
                                                                                                                                                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                            :> Put
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                                                             :<|> Named
                                                                                                                                                    '("ipatch",
                                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                    (Description
                                                                                                                                                       ""
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                                 :> Patch
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                                                      :<|> ((Named
                                                                                                                                               '("iget",
                                                                                                                                                 OutlookCalIntegrationConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Get config for outlookCalIntegration"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("outlookCalIntegration"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        OutlookCalIntegrationConfig))))))))))
                                                                                                                                             :<|> (Named
                                                                                                                                                     '("iput",
                                                                                                                                                       OutlookCalIntegrationConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Put config for outlookCalIntegration"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                          :> (CanThrowMany
                                                                                                                                                                                '[]
                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                        "tid"
                                                                                                                                                                                        TeamId
                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                          :> ("outlookCalIntegration"
                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (Feature
                                                                                                                                                                                                       OutlookCalIntegrationConfig)
                                                                                                                                                                                                  :> Put
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          OutlookCalIntegrationConfig)))))))))))))
                                                                                                                                                   :<|> Named
                                                                                                                                                          '("ipatch",
                                                                                                                                                            OutlookCalIntegrationConfig)
                                                                                                                                                          (Description
                                                                                                                                                             ""
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Patch config for outlookCalIntegration"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('MissingPermission
                                                                                                                                                                        'Nothing)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 TeamFeatureError
                                                                                                                                                                               :> (CanThrowMany
                                                                                                                                                                                     '[]
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> ("outlookCalIntegration"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                                                                            OutlookCalIntegrationConfig)
                                                                                                                                                                                                       :> Patch
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               OutlookCalIntegrationConfig)))))))))))))))
                                                                                                                                            :<|> ((Named
                                                                                                                                                     '("iget",
                                                                                                                                                       MlsE2EIdConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Get config for mlsE2EId"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("mlsE2EId"
                                                                                                                                                                                      :> Get
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              MlsE2EIdConfig))))))))))
                                                                                                                                                   :<|> (Named
                                                                                                                                                           '("iput",
                                                                                                                                                             MlsE2EIdConfig)
                                                                                                                                                           (Description
                                                                                                                                                              ""
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Put config for mlsE2EId"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  TeamFeatureError
                                                                                                                                                                                :> (CanThrowMany
                                                                                                                                                                                      '[]
                                                                                                                                                                                    :> ("teams"
                                                                                                                                                                                        :> (Capture
                                                                                                                                                                                              "tid"
                                                                                                                                                                                              TeamId
                                                                                                                                                                                            :> ("features"
                                                                                                                                                                                                :> ("mlsE2EId"
                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (Feature
                                                                                                                                                                                                             MlsE2EIdConfig)
                                                                                                                                                                                                        :> Put
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                MlsE2EIdConfig)))))))))))))
                                                                                                                                                         :<|> Named
                                                                                                                                                                '("ipatch",
                                                                                                                                                                  MlsE2EIdConfig)
                                                                                                                                                                (Description
                                                                                                                                                                   ""
                                                                                                                                                                 :> (Summary
                                                                                                                                                                       "Patch config for mlsE2EId"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('MissingPermission
                                                                                                                                                                              'Nothing)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       TeamFeatureError
                                                                                                                                                                                     :> (CanThrowMany
                                                                                                                                                                                           '[]
                                                                                                                                                                                         :> ("teams"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "tid"
                                                                                                                                                                                                   TeamId
                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                     :> ("mlsE2EId"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                                                                  MlsE2EIdConfig)
                                                                                                                                                                                                             :> Patch
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     MlsE2EIdConfig)))))))))))))))
                                                                                                                                                  :<|> ((Named
                                                                                                                                                           '("iget",
                                                                                                                                                             MlsMigrationConfig)
                                                                                                                                                           (Description
                                                                                                                                                              ""
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Get config for mlsMigration"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                :> (Capture
                                                                                                                                                                                      "tid"
                                                                                                                                                                                      TeamId
                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                        :> ("mlsMigration"
                                                                                                                                                                                            :> Get
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    MlsMigrationConfig))))))))))
                                                                                                                                                         :<|> (Named
                                                                                                                                                                 '("iput",
                                                                                                                                                                   MlsMigrationConfig)
                                                                                                                                                                 (Description
                                                                                                                                                                    ""
                                                                                                                                                                  :> (Summary
                                                                                                                                                                        "Put config for mlsMigration"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            ('MissingPermission
                                                                                                                                                                               'Nothing)
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        TeamFeatureError
                                                                                                                                                                                      :> (CanThrowMany
                                                                                                                                                                                            '[]
                                                                                                                                                                                          :> ("teams"
                                                                                                                                                                                              :> (Capture
                                                                                                                                                                                                    "tid"
                                                                                                                                                                                                    TeamId
                                                                                                                                                                                                  :> ("features"
                                                                                                                                                                                                      :> ("mlsMigration"
                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (Feature
                                                                                                                                                                                                                   MlsMigrationConfig)
                                                                                                                                                                                                              :> Put
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                                      MlsMigrationConfig)))))))))))))
                                                                                                                                                               :<|> Named
                                                                                                                                                                      '("ipatch",
                                                                                                                                                                        MlsMigrationConfig)
                                                                                                                                                                      (Description
                                                                                                                                                                         ""
                                                                                                                                                                       :> (Summary
                                                                                                                                                                             "Patch config for mlsMigration"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('MissingPermission
                                                                                                                                                                                    'Nothing)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             TeamFeatureError
                                                                                                                                                                                           :> (CanThrowMany
                                                                                                                                                                                                 '[]
                                                                                                                                                                                               :> ("teams"
                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                         "tid"
                                                                                                                                                                                                         TeamId
                                                                                                                                                                                                       :> ("features"
                                                                                                                                                                                                           :> ("mlsMigration"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                                                                        MlsMigrationConfig)
                                                                                                                                                                                                                   :> Patch
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                           MlsMigrationConfig)))))))))))))))
                                                                                                                                                        :<|> ((Named
                                                                                                                                                                 '("iget",
                                                                                                                                                                   EnforceFileDownloadLocationConfig)
                                                                                                                                                                 (Description
                                                                                                                                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                  :> (Summary
                                                                                                                                                                        "Get config for enforceFileDownloadLocation"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            ('MissingPermission
                                                                                                                                                                               'Nothing)
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> ("teams"
                                                                                                                                                                                      :> (Capture
                                                                                                                                                                                            "tid"
                                                                                                                                                                                            TeamId
                                                                                                                                                                                          :> ("features"
                                                                                                                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                  :> Get
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                                               :<|> (Named
                                                                                                                                                                       '("iput",
                                                                                                                                                                         EnforceFileDownloadLocationConfig)
                                                                                                                                                                       (Description
                                                                                                                                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                        :> (Summary
                                                                                                                                                                              "Put config for enforceFileDownloadLocation"
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  ('MissingPermission
                                                                                                                                                                                     'Nothing)
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              TeamFeatureError
                                                                                                                                                                                            :> (CanThrowMany
                                                                                                                                                                                                  '[]
                                                                                                                                                                                                :> ("teams"
                                                                                                                                                                                                    :> (Capture
                                                                                                                                                                                                          "tid"
                                                                                                                                                                                                          TeamId
                                                                                                                                                                                                        :> ("features"
                                                                                                                                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (Feature
                                                                                                                                                                                                                         EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                                    :> Put
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                                                            EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                                                     :<|> Named
                                                                                                                                                                            '("ipatch",
                                                                                                                                                                              EnforceFileDownloadLocationConfig)
                                                                                                                                                                            (Description
                                                                                                                                                                               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                             :> (Summary
                                                                                                                                                                                   "Patch config for enforceFileDownloadLocation"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('MissingPermission
                                                                                                                                                                                          'Nothing)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   TeamFeatureError
                                                                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                                                                       '[]
                                                                                                                                                                                                     :> ("teams"
                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                               "tid"
                                                                                                                                                                                                               TeamId
                                                                                                                                                                                                             :> ("features"
                                                                                                                                                                                                                 :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                                                                              EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                                         :> Patch
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                 EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                                              :<|> (Named
                                                                                                                                                                      '("iget",
                                                                                                                                                                        LimitedEventFanoutConfig)
                                                                                                                                                                      (Description
                                                                                                                                                                         ""
                                                                                                                                                                       :> (Summary
                                                                                                                                                                             "Get config for limitedEventFanout"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('MissingPermission
                                                                                                                                                                                    'Nothing)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("teams"
                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                 "tid"
                                                                                                                                                                                                 TeamId
                                                                                                                                                                                               :> ("features"
                                                                                                                                                                                                   :> ("limitedEventFanout"
                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               LimitedEventFanoutConfig))))))))))
                                                                                                                                                                    :<|> (Named
                                                                                                                                                                            '("iput",
                                                                                                                                                                              LimitedEventFanoutConfig)
                                                                                                                                                                            (Description
                                                                                                                                                                               ""
                                                                                                                                                                             :> (Summary
                                                                                                                                                                                   "Put config for limitedEventFanout"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('MissingPermission
                                                                                                                                                                                          'Nothing)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   TeamFeatureError
                                                                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                                                                       '[]
                                                                                                                                                                                                     :> ("teams"
                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                               "tid"
                                                                                                                                                                                                               TeamId
                                                                                                                                                                                                             :> ("features"
                                                                                                                                                                                                                 :> ("limitedEventFanout"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           (Feature
                                                                                                                                                                                                                              LimitedEventFanoutConfig)
                                                                                                                                                                                                                         :> Put
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                 LimitedEventFanoutConfig)))))))))))))
                                                                                                                                                                          :<|> Named
                                                                                                                                                                                 '("ipatch",
                                                                                                                                                                                   LimitedEventFanoutConfig)
                                                                                                                                                                                 (Description
                                                                                                                                                                                    ""
                                                                                                                                                                                  :> (Summary
                                                                                                                                                                                        "Patch config for limitedEventFanout"
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            ('MissingPermission
                                                                                                                                                                                               'Nothing)
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                        TeamFeatureError
                                                                                                                                                                                                      :> (CanThrowMany
                                                                                                                                                                                                            '[]
                                                                                                                                                                                                          :> ("teams"
                                                                                                                                                                                                              :> (Capture
                                                                                                                                                                                                                    "tid"
                                                                                                                                                                                                                    TeamId
                                                                                                                                                                                                                  :> ("features"
                                                                                                                                                                                                                      :> ("limitedEventFanout"
                                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                (LockableFeaturePatch
                                                                                                                                                                                                                                   LimitedEventFanoutConfig)
                                                                                                                                                                                                                              :> Patch
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                                                      LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                                                 :<|> (Named
                                                         '("ilock", FileSharingConfig)
                                                         (Summary "(Un-)lock fileSharing"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("fileSharing"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock", ConferenceCallingConfig)
                                                               (Summary
                                                                  "(Un-)lock conferenceCalling"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("conferenceCalling"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock",
                                                                       SelfDeletingMessagesConfig)
                                                                     (Summary
                                                                        "(Un-)lock selfDeletingMessages"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("selfDeletingMessages"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock",
                                                                             GuestLinksConfig)
                                                                           (Summary
                                                                              "(Un-)lock conversationGuestLinks"
                                                                            :> (Description ""
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("conversationGuestLinks"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("ilock",
                                                                                   SndFactorPasswordChallengeConfig)
                                                                                 (Summary
                                                                                    "(Un-)lock sndFactorPasswordChallenge"
                                                                                  :> (Description ""
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("sndFactorPasswordChallenge"
                                                                                                              :> (Capture
                                                                                                                    "lockStatus"
                                                                                                                    LockStatus
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       LockStatusResponse)))))))))
                                                                               :<|> (Named
                                                                                       '("ilock",
                                                                                         MLSConfig)
                                                                                       (Summary
                                                                                          "(Un-)lock mls"
                                                                                        :> (Description
                                                                                              ""
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mls"
                                                                                                                    :> (Capture
                                                                                                                          "lockStatus"
                                                                                                                          LockStatus
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             LockStatusResponse)))))))))
                                                                                     :<|> (Named
                                                                                             '("ilock",
                                                                                               OutlookCalIntegrationConfig)
                                                                                             (Summary
                                                                                                "(Un-)lock outlookCalIntegration"
                                                                                              :> (Description
                                                                                                    ""
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("outlookCalIntegration"
                                                                                                                          :> (Capture
                                                                                                                                "lockStatus"
                                                                                                                                LockStatus
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   LockStatusResponse)))))))))
                                                                                           :<|> (Named
                                                                                                   '("ilock",
                                                                                                     MlsE2EIdConfig)
                                                                                                   (Summary
                                                                                                      "(Un-)lock mlsE2EId"
                                                                                                    :> (Description
                                                                                                          ""
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mlsE2EId"
                                                                                                                                :> (Capture
                                                                                                                                      "lockStatus"
                                                                                                                                      LockStatus
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         LockStatusResponse)))))))))
                                                                                                 :<|> (Named
                                                                                                         '("ilock",
                                                                                                           MlsMigrationConfig)
                                                                                                         (Summary
                                                                                                            "(Un-)lock mlsMigration"
                                                                                                          :> (Description
                                                                                                                ""
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("mlsMigration"
                                                                                                                                      :> (Capture
                                                                                                                                            "lockStatus"
                                                                                                                                            LockStatus
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               LockStatusResponse)))))))))
                                                                                                       :<|> (Named
                                                                                                               '("ilock",
                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                               (Summary
                                                                                                                  "(Un-)lock enforceFileDownloadLocation"
                                                                                                                :> (Description
                                                                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("enforceFileDownloadLocation"
                                                                                                                                            :> (Capture
                                                                                                                                                  "lockStatus"
                                                                                                                                                  LockStatus
                                                                                                                                                :> Put
                                                                                                                                                     '[JSON]
                                                                                                                                                     LockStatusResponse)))))))))
                                                                                                             :<|> (Named
                                                                                                                     '("igetmulti",
                                                                                                                       SearchVisibilityInboundConfig)
                                                                                                                     (Summary
                                                                                                                        "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                                                      :> ("features-multi-teams"
                                                                                                                          :> ("searchVisibilityInbound"
                                                                                                                              :> (ReqBody
                                                                                                                                    '[JSON]
                                                                                                                                    TeamFeatureNoConfigMultiRequest
                                                                                                                                  :> Post
                                                                                                                                       '[JSON]
                                                                                                                                       (TeamFeatureNoConfigMultiResponse
                                                                                                                                          SearchVisibilityInboundConfig)))))
                                                                                                                   :<|> Named
                                                                                                                          "feature-configs-internal"
                                                                                                                          (Summary
                                                                                                                             "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> (CanThrow
                                                                                                                                     ('MissingPermission
                                                                                                                                        'Nothing)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotATeamMember
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TeamNotFound
                                                                                                                                           :> (QueryParam'
                                                                                                                                                 '[Optional,
                                                                                                                                                   Strict,
                                                                                                                                                   Description
                                                                                                                                                     "Optional user id"]
                                                                                                                                                 "user_id"
                                                                                                                                                 UserId
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    AllTeamFeatures))))))))))))))))))
                                                :<|> (IFederationAPI
                                                      :<|> (IConversationAPI :<|> IEJPDAPI))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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-user"
        (Summary
           "Remove a user from their teams and conversations and erase their clients"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (ZLocalUser
                     :> (ZOptConn
                         :> ("user"
                             :> MultiVerb
                                  'DELETE
                                  '[JSON]
                                  '[RespondEmpty 200 "Remove a user from Galley"]
                                  ()))))))
      :<|> (Named
              "connect"
              (Summary "Create a connect conversation (deprecated)"
               :> (MakesFederatedCall 'Brig "api-version"
                   :> (MakesFederatedCall 'Galley "on-conversation-created"
                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'InvalidOperation
                                   :> (CanThrow 'NotConnected
                                       :> (CanThrow UnreachableBackends
                                           :> (ZLocalUser
                                               :> (ZOptConn
                                                   :> ("conversations"
                                                       :> ("connect"
                                                           :> (ReqBody '[JSON] Connect
                                                               :> 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-conversation-clients"
                    (Summary "Get mls conversation client list"
                     :> (CanThrow 'ConvNotFound
                         :> ("group"
                             :> (Capture "gid" GroupId
                                 :> MultiVerb
                                      'GET
                                      '[JSON]
                                      '[Respond 200 "Clients" ClientList]
                                      ClientList))))
                  :<|> (Named
                          "guard-legalhold-policy-conflicts"
                          ("guard-legalhold-policy-conflicts"
                           :> (CanThrow 'MissingLegalholdConsent
                               :> (CanThrow 'MissingLegalholdConsentOldClients
                                   :> (ReqBody '[JSON] GuardLegalholdPolicyConflicts
                                       :> MultiVerb
                                            'PUT
                                            '[JSON]
                                            '[RespondEmpty 200 "Guard Legalhold Policy"]
                                            ()))))
                        :<|> (("legalhold"
                               :> ("whitelisted-teams"
                                   :> (Capture "tid" TeamId
                                       :> (Named
                                             "set-team-legalhold-whitelisted"
                                             (MultiVerb
                                                'PUT
                                                '[JSON]
                                                '[RespondEmpty 200 "Team Legalhold Whitelisted"]
                                                ())
                                           :<|> (Named
                                                   "unset-team-legalhold-whitelisted"
                                                   (MultiVerb
                                                      'DELETE
                                                      '[JSON]
                                                      '[RespondEmpty
                                                          204 "Team Legalhold un-Whitelisted"]
                                                      ())
                                                 :<|> Named
                                                        "get-team-legalhold-whitelisted"
                                                        (MultiVerb
                                                           'GET
                                                           '[JSON]
                                                           '[RespondEmpty
                                                               404 "Team not Legalhold Whitelisted",
                                                             RespondEmpty
                                                               200 "Team Legalhold Whitelisted"]
                                                           Bool))))))
                              :<|> (("teams"
                                     :> (Capture "tid" TeamId
                                         :> (Named
                                               "get-team-internal"
                                               (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
                                             :<|> (Named
                                                     "create-binding-team"
                                                     (ZUser
                                                      :> (ReqBody '[JSON] BindingNewTeam
                                                          :> MultiVerb
                                                               'PUT
                                                               '[JSON]
                                                               '[WithHeaders
                                                                   '[Header "Location" TeamId]
                                                                   TeamId
                                                                   (RespondEmpty 201 "OK")]
                                                               TeamId))
                                                   :<|> (Named
                                                           "delete-binding-team"
                                                           (CanThrow 'NoBindingTeam
                                                            :> (CanThrow 'NotAOneMemberTeam
                                                                :> (CanThrow 'DeleteQueueFull
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> (QueryFlag "force"
                                                                            :> MultiVerb
                                                                                 'DELETE
                                                                                 '[JSON]
                                                                                 '[RespondEmpty
                                                                                     202 "OK"]
                                                                                 ())))))
                                                         :<|> (Named
                                                                 "get-team-name"
                                                                 ("name"
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> Get '[JSON] TeamName))
                                                               :<|> (Named
                                                                       "update-team-status"
                                                                       ("status"
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  'InvalidTeamStatusUpdate
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      TeamStatusUpdate
                                                                                    :> MultiVerb
                                                                                         'PUT
                                                                                         '[JSON]
                                                                                         '[RespondEmpty
                                                                                             200
                                                                                             "OK"]
                                                                                         ()))))
                                                                     :<|> (("members"
                                                                            :> (Named
                                                                                  "unchecked-add-team-member"
                                                                                  (CanThrow
                                                                                     'TooManyTeamMembers
                                                                                   :> (CanThrow
                                                                                         'TooManyTeamMembersOnTeamWithLegalhold
                                                                                       :> (CanThrow
                                                                                             'TooManyTeamAdmins
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 NewTeamMember
                                                                                               :> MultiVerb
                                                                                                    'POST
                                                                                                    '[JSON]
                                                                                                    '[RespondEmpty
                                                                                                        200
                                                                                                        "OK"]
                                                                                                    ()))))
                                                                                :<|> (Named
                                                                                        "unchecked-get-team-members"
                                                                                        (QueryParam'
                                                                                           '[Strict]
                                                                                           "maxResults"
                                                                                           (Range
                                                                                              1
                                                                                              HardTruncationLimit
                                                                                              Int32)
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              TeamMemberList)
                                                                                      :<|> (Named
                                                                                              "unchecked-get-team-member"
                                                                                              (Capture
                                                                                                 "uid"
                                                                                                 UserId
                                                                                               :> (CanThrow
                                                                                                     'TeamMemberNotFound
                                                                                                   :> Get
                                                                                                        '[JSON]
                                                                                                        TeamMember))
                                                                                            :<|> (Named
                                                                                                    "can-user-join-team"
                                                                                                    ("check"
                                                                                                     :> (CanThrow
                                                                                                           'TooManyTeamMembersOnTeamWithLegalhold
                                                                                                         :> MultiVerb
                                                                                                              'GET
                                                                                                              '[JSON]
                                                                                                              '[RespondEmpty
                                                                                                                  200
                                                                                                                  "User can join"]
                                                                                                              ()))
                                                                                                  :<|> Named
                                                                                                         "unchecked-update-team-member"
                                                                                                         (CanThrow
                                                                                                            'AccessDenied
                                                                                                          :> (CanThrow
                                                                                                                'InvalidPermissions
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamMemberNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            'TooManyTeamAdmins
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    ('MissingPermission
                                                                                                                                       'Nothing)
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        NewTeamMember
                                                                                                                                      :> MultiVerb
                                                                                                                                           'PUT
                                                                                                                                           '[JSON]
                                                                                                                                           '[RespondEmpty
                                                                                                                                               200
                                                                                                                                               ""]
                                                                                                                                           ())))))))))))))
                                                                           :<|> (Named
                                                                                   "user-is-team-owner"
                                                                                   ("is-team-owner"
                                                                                    :> (Capture
                                                                                          "uid"
                                                                                          UserId
                                                                                        :> (CanThrow
                                                                                              'AccessDenied
                                                                                            :> (CanThrow
                                                                                                  'TeamMemberNotFound
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> MultiVerb
                                                                                                         'GET
                                                                                                         '[JSON]
                                                                                                         '[RespondEmpty
                                                                                                             200
                                                                                                             "User is team owner"]
                                                                                                         ())))))
                                                                                 :<|> ("search-visibility"
                                                                                       :> (Named
                                                                                             "get-search-visibility-internal"
                                                                                             (Get
                                                                                                '[JSON]
                                                                                                TeamSearchVisibilityView)
                                                                                           :<|> Named
                                                                                                  "set-search-visibility-internal"
                                                                                                  (CanThrow
                                                                                                     'TeamSearchVisibilityNotEnabled
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     TeamSearchVisibilityView
                                                                                                                   :> MultiVerb
                                                                                                                        'PUT
                                                                                                                        '[JSON]
                                                                                                                        '[RespondEmpty
                                                                                                                            204
                                                                                                                            "OK"]
                                                                                                                        ()))))))))))))))))
                                    :<|> ((Named
                                             "get-team-members"
                                             (CanThrow 'NonBindingTeam
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("users"
                                                      :> (Capture "uid" UserId
                                                          :> ("team"
                                                              :> ("members"
                                                                  :> Get
                                                                       '[JSON] TeamMemberList))))))
                                           :<|> (Named
                                                   "get-team-id"
                                                   (CanThrow 'NonBindingTeam
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("users"
                                                            :> (Capture "uid" UserId
                                                                :> ("team"
                                                                    :> Get '[JSON] TeamId)))))
                                                 :<|> (Named
                                                         "test-get-clients"
                                                         ("test"
                                                          :> ("clients"
                                                              :> (ZUser :> Get '[JSON] [ClientId])))
                                                       :<|> (Named
                                                               "test-add-client"
                                                               ("clients"
                                                                :> (ZUser
                                                                    :> (Capture "cid" ClientId
                                                                        :> MultiVerb
                                                                             'POST
                                                                             '[JSON]
                                                                             '[RespondEmpty
                                                                                 200 "OK"]
                                                                             ())))
                                                             :<|> (Named
                                                                     "test-delete-client"
                                                                     ("clients"
                                                                      :> (ZUser
                                                                          :> (Capture "cid" ClientId
                                                                              :> MultiVerb
                                                                                   'DELETE
                                                                                   '[JSON]
                                                                                   '[RespondEmpty
                                                                                       200 "OK"]
                                                                                   ())))
                                                                   :<|> (Named
                                                                           "add-service"
                                                                           ("services"
                                                                            :> (ReqBody
                                                                                  '[JSON] Service
                                                                                :> MultiVerb
                                                                                     'POST
                                                                                     '[JSON]
                                                                                     '[RespondEmpty
                                                                                         200 "OK"]
                                                                                     ()))
                                                                         :<|> (Named
                                                                                 "delete-service"
                                                                                 ("services"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        ServiceRef
                                                                                      :> MultiVerb
                                                                                           'DELETE
                                                                                           '[JSON]
                                                                                           '[RespondEmpty
                                                                                               200
                                                                                               "OK"]
                                                                                           ()))
                                                                               :<|> (Named
                                                                                       "i-add-bot"
                                                                                       (CanThrow
                                                                                          ('ActionDenied
                                                                                             'AddConversationMember)
                                                                                        :> (CanThrow
                                                                                              'ConvNotFound
                                                                                            :> (CanThrow
                                                                                                  'InvalidOperation
                                                                                                :> (CanThrow
                                                                                                      'TooManyMembers
                                                                                                    :> ("bots"
                                                                                                        :> (ZLocalUser
                                                                                                            :> (ZConn
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      AddBot
                                                                                                                    :> Post
                                                                                                                         '[JSON]
                                                                                                                         Event))))))))
                                                                                     :<|> (Named
                                                                                             "delete-bot"
                                                                                             (CanThrow
                                                                                                'ConvNotFound
                                                                                              :> (CanThrow
                                                                                                    ('ActionDenied
                                                                                                       'RemoveConversationMember)
                                                                                                  :> ("bots"
                                                                                                      :> (ZLocalUser
                                                                                                          :> (ZOptConn
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    RemoveBot
                                                                                                                  :> MultiVerb
                                                                                                                       'DELETE
                                                                                                                       '[JSON]
                                                                                                                       (UpdateResponses
                                                                                                                          "Bot not found"
                                                                                                                          "Bot deleted"
                                                                                                                          Event)
                                                                                                                       (UpdateResult
                                                                                                                          Event)))))))
                                                                                           :<|> (Named
                                                                                                   "put-custom-backend"
                                                                                                   ("custom-backend"
                                                                                                    :> ("by-domain"
                                                                                                        :> (Capture
                                                                                                              "domain"
                                                                                                              Domain
                                                                                                            :> (ReqBody
                                                                                                                  '[JSON]
                                                                                                                  CustomBackend
                                                                                                                :> MultiVerb
                                                                                                                     'PUT
                                                                                                                     '[JSON]
                                                                                                                     '[RespondEmpty
                                                                                                                         201
                                                                                                                         "OK"]
                                                                                                                     ()))))
                                                                                                 :<|> Named
                                                                                                        "delete-custom-backend"
                                                                                                        ("custom-backend"
                                                                                                         :> ("by-domain"
                                                                                                             :> (Capture
                                                                                                                   "domain"
                                                                                                                   Domain
                                                                                                                 :> MultiVerb
                                                                                                                      'DELETE
                                                                                                                      '[JSON]
                                                                                                                      '[RespondEmpty
                                                                                                                          200
                                                                                                                          "OK"]
                                                                                                                      ())))))))))))))
                                          :<|> (Named
                                                  "upsert-one2one"
                                                  (Summary
                                                     "Create or Update a connect or one2one conversation."
                                                   :> ("conversations"
                                                       :> ("one2one"
                                                           :> ("upsert"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     UpsertOne2OneConversationRequest
                                                                   :> MultiVerb
                                                                        'POST
                                                                        '[JSON]
                                                                        '[RespondEmpty
                                                                            200
                                                                            "Upsert One2One Policy"]
                                                                        ())))))
                                                :<|> ((((Named
                                                           '("iget", LegalholdConfig)
                                                           (Description ""
                                                            :> (Summary "Get config for legalhold"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("legalhold"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    LegalholdConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput", LegalholdConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Put config for legalhold"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[ 'ActionDenied
                                                                                                 'RemoveConversationMember,
                                                                                               'CannotEnableLegalHoldServiceLargeTeam,
                                                                                               'LegalHoldNotEnabled,
                                                                                               'LegalHoldDisableUnimplemented,
                                                                                               'LegalHoldServiceNotRegistered,
                                                                                               'UserLegalHoldIllegalOperation,
                                                                                               'LegalHoldCouldNotBlockConnections]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("legalhold"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   LegalholdConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      LegalholdConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch", LegalholdConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for legalhold"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[ 'ActionDenied
                                                                                                      'RemoveConversationMember,
                                                                                                    'CannotEnableLegalHoldServiceLargeTeam,
                                                                                                    'LegalHoldNotEnabled,
                                                                                                    'LegalHoldDisableUnimplemented,
                                                                                                    'LegalHoldServiceNotRegistered,
                                                                                                    'UserLegalHoldIllegalOperation,
                                                                                                    'LegalHoldCouldNotBlockConnections]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("legalhold"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        LegalholdConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           LegalholdConfig)))))))))))))))
                                                        :<|> ((Named
                                                                 '("iget", SSOConfig)
                                                                 (Description ""
                                                                  :> (Summary "Get config for sso"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("sso"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          SSOConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput", SSOConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for sso"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("sso"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         SSOConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            SSOConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch", SSOConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for sso"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("sso"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              SSOConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 SSOConfig)))))))))))))))
                                                              :<|> ((Named
                                                                       '("iget",
                                                                         SearchVisibilityAvailableConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for searchVisibility"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("searchVisibility"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SearchVisibilityAvailableConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               SearchVisibilityAvailableConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for searchVisibility"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("searchVisibility"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               SearchVisibilityAvailableConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  SearchVisibilityAvailableConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    SearchVisibilityAvailableConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for searchVisibility"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("searchVisibility"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    SearchVisibilityAvailableConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       SearchVisibilityAvailableConfig)))))))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               SearchVisibilityInboundConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for searchVisibilityInbound"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("searchVisibilityInbound"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      SearchVisibilityInboundConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     SearchVisibilityInboundConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for searchVisibilityInbound"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("searchVisibilityInbound"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     SearchVisibilityInboundConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        SearchVisibilityInboundConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          SearchVisibilityInboundConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for searchVisibilityInbound"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("searchVisibilityInbound"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          SearchVisibilityInboundConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             SearchVisibilityInboundConfig)))))))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     ValidateSAMLEmailsConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for validateSAMLemails"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("validateSAMLemails"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            ValidateSAMLEmailsConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           ValidateSAMLEmailsConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for validateSAMLemails"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("validateSAMLemails"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           ValidateSAMLEmailsConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              ValidateSAMLEmailsConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                ValidateSAMLEmailsConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for validateSAMLemails"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("validateSAMLemails"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                ValidateSAMLEmailsConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   ValidateSAMLEmailsConfig)))))))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           DigitalSignaturesConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for digitalSignatures"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("digitalSignatures"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  DigitalSignaturesConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 DigitalSignaturesConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for digitalSignatures"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("digitalSignatures"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 DigitalSignaturesConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    DigitalSignaturesConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      DigitalSignaturesConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for digitalSignatures"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("digitalSignatures"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      DigitalSignaturesConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         DigitalSignaturesConfig)))))))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 AppLockConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for appLock"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("appLock"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        AppLockConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       AppLockConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for appLock"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("appLock"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       AppLockConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          AppLockConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            AppLockConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for appLock"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("appLock"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            AppLockConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               AppLockConfig)))))))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       FileSharingConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for fileSharing"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("fileSharing"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              FileSharingConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             FileSharingConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for fileSharing"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("fileSharing"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             FileSharingConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                FileSharingConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  FileSharingConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for fileSharing"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("fileSharing"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  FileSharingConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     FileSharingConfig)))))))))))))))
                                                                                                  :<|> (Named
                                                                                                          '("iget",
                                                                                                            ClassifiedDomainsConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Get config for classifiedDomains"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("classifiedDomains"
                                                                                                                                           :> Get
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   ClassifiedDomainsConfig))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   ConferenceCallingConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for conferenceCalling"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("conferenceCalling"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          ConferenceCallingConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         ConferenceCallingConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for conferenceCalling"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("conferenceCalling"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         ConferenceCallingConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            ConferenceCallingConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              ConferenceCallingConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for conferenceCalling"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("conferenceCalling"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              ConferenceCallingConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 ConferenceCallingConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         SelfDeletingMessagesConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for selfDeletingMessages"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("selfDeletingMessages"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                SelfDeletingMessagesConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               SelfDeletingMessagesConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for selfDeletingMessages"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("selfDeletingMessages"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               SelfDeletingMessagesConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  SelfDeletingMessagesConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    SelfDeletingMessagesConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for selfDeletingMessages"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("selfDeletingMessages"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    SelfDeletingMessagesConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       SelfDeletingMessagesConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               GuestLinksConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for conversationGuestLinks"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("conversationGuestLinks"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      GuestLinksConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     GuestLinksConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for conversationGuestLinks"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("conversationGuestLinks"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     GuestLinksConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        GuestLinksConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          GuestLinksConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for conversationGuestLinks"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          GuestLinksConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             GuestLinksConfig)))))))))))))))
                                                                                                                          :<|> ((Named
                                                                                                                                   '("iget",
                                                                                                                                     SndFactorPasswordChallengeConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for sndFactorPasswordChallenge"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("sndFactorPasswordChallenge"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                 :<|> (Named
                                                                                                                                         '("iput",
                                                                                                                                           SndFactorPasswordChallengeConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Put config for sndFactorPasswordChallenge"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Feature
                                                                                                                                                                                           SndFactorPasswordChallengeConfig)
                                                                                                                                                                                      :> Put
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              SndFactorPasswordChallengeConfig)))))))))))))
                                                                                                                                       :<|> Named
                                                                                                                                              '("ipatch",
                                                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Patch config for sndFactorPasswordChallenge"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                                                                :<|> ((Named
                                                                                                                                         '("iget",
                                                                                                                                           MLSConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for mls"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("mls"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  MLSConfig))))))))))
                                                                                                                                       :<|> (Named
                                                                                                                                               '("iput",
                                                                                                                                                 MLSConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Put config for mls"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                          '[]
                                                                                                                                                                        :> ("teams"
                                                                                                                                                                            :> (Capture
                                                                                                                                                                                  "tid"
                                                                                                                                                                                  TeamId
                                                                                                                                                                                :> ("features"
                                                                                                                                                                                    :> ("mls"
                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (Feature
                                                                                                                                                                                                 MLSConfig)
                                                                                                                                                                                            :> Put
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    MLSConfig)))))))))))))
                                                                                                                                             :<|> Named
                                                                                                                                                    '("ipatch",
                                                                                                                                                      MLSConfig)
                                                                                                                                                    (Description
                                                                                                                                                       ""
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Patch config for mls"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("mls"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                                                      MLSConfig)
                                                                                                                                                                                                 :> Patch
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         MLSConfig)))))))))))))))
                                                                                                                                      :<|> ((Named
                                                                                                                                               '("iget",
                                                                                                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                                                             :<|> (Named
                                                                                                                                                     '("iput",
                                                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                          :> (CanThrowMany
                                                                                                                                                                                '[]
                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                        "tid"
                                                                                                                                                                                        TeamId
                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (Feature
                                                                                                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                                  :> Put
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                                                                   :<|> Named
                                                                                                                                                          '("ipatch",
                                                                                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                          (Description
                                                                                                                                                             ""
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('MissingPermission
                                                                                                                                                                        'Nothing)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 TeamFeatureError
                                                                                                                                                                               :> (CanThrowMany
                                                                                                                                                                                     '[]
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                                       :> Patch
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                                                            :<|> ((Named
                                                                                                                                                     '("iget",
                                                                                                                                                       OutlookCalIntegrationConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Get config for outlookCalIntegration"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("outlookCalIntegration"
                                                                                                                                                                                      :> Get
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              OutlookCalIntegrationConfig))))))))))
                                                                                                                                                   :<|> (Named
                                                                                                                                                           '("iput",
                                                                                                                                                             OutlookCalIntegrationConfig)
                                                                                                                                                           (Description
                                                                                                                                                              ""
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Put config for outlookCalIntegration"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  TeamFeatureError
                                                                                                                                                                                :> (CanThrowMany
                                                                                                                                                                                      '[]
                                                                                                                                                                                    :> ("teams"
                                                                                                                                                                                        :> (Capture
                                                                                                                                                                                              "tid"
                                                                                                                                                                                              TeamId
                                                                                                                                                                                            :> ("features"
                                                                                                                                                                                                :> ("outlookCalIntegration"
                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (Feature
                                                                                                                                                                                                             OutlookCalIntegrationConfig)
                                                                                                                                                                                                        :> Put
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                OutlookCalIntegrationConfig)))))))))))))
                                                                                                                                                         :<|> Named
                                                                                                                                                                '("ipatch",
                                                                                                                                                                  OutlookCalIntegrationConfig)
                                                                                                                                                                (Description
                                                                                                                                                                   ""
                                                                                                                                                                 :> (Summary
                                                                                                                                                                       "Patch config for outlookCalIntegration"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('MissingPermission
                                                                                                                                                                              'Nothing)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       TeamFeatureError
                                                                                                                                                                                     :> (CanThrowMany
                                                                                                                                                                                           '[]
                                                                                                                                                                                         :> ("teams"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "tid"
                                                                                                                                                                                                   TeamId
                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                     :> ("outlookCalIntegration"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                                                                  OutlookCalIntegrationConfig)
                                                                                                                                                                                                             :> Patch
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     OutlookCalIntegrationConfig)))))))))))))))
                                                                                                                                                  :<|> ((Named
                                                                                                                                                           '("iget",
                                                                                                                                                             MlsE2EIdConfig)
                                                                                                                                                           (Description
                                                                                                                                                              ""
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Get config for mlsE2EId"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                :> (Capture
                                                                                                                                                                                      "tid"
                                                                                                                                                                                      TeamId
                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                        :> ("mlsE2EId"
                                                                                                                                                                                            :> Get
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    MlsE2EIdConfig))))))))))
                                                                                                                                                         :<|> (Named
                                                                                                                                                                 '("iput",
                                                                                                                                                                   MlsE2EIdConfig)
                                                                                                                                                                 (Description
                                                                                                                                                                    ""
                                                                                                                                                                  :> (Summary
                                                                                                                                                                        "Put config for mlsE2EId"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            ('MissingPermission
                                                                                                                                                                               'Nothing)
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        TeamFeatureError
                                                                                                                                                                                      :> (CanThrowMany
                                                                                                                                                                                            '[]
                                                                                                                                                                                          :> ("teams"
                                                                                                                                                                                              :> (Capture
                                                                                                                                                                                                    "tid"
                                                                                                                                                                                                    TeamId
                                                                                                                                                                                                  :> ("features"
                                                                                                                                                                                                      :> ("mlsE2EId"
                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (Feature
                                                                                                                                                                                                                   MlsE2EIdConfig)
                                                                                                                                                                                                              :> Put
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                                      MlsE2EIdConfig)))))))))))))
                                                                                                                                                               :<|> Named
                                                                                                                                                                      '("ipatch",
                                                                                                                                                                        MlsE2EIdConfig)
                                                                                                                                                                      (Description
                                                                                                                                                                         ""
                                                                                                                                                                       :> (Summary
                                                                                                                                                                             "Patch config for mlsE2EId"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('MissingPermission
                                                                                                                                                                                    'Nothing)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             TeamFeatureError
                                                                                                                                                                                           :> (CanThrowMany
                                                                                                                                                                                                 '[]
                                                                                                                                                                                               :> ("teams"
                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                         "tid"
                                                                                                                                                                                                         TeamId
                                                                                                                                                                                                       :> ("features"
                                                                                                                                                                                                           :> ("mlsE2EId"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                                                                        MlsE2EIdConfig)
                                                                                                                                                                                                                   :> Patch
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                           MlsE2EIdConfig)))))))))))))))
                                                                                                                                                        :<|> ((Named
                                                                                                                                                                 '("iget",
                                                                                                                                                                   MlsMigrationConfig)
                                                                                                                                                                 (Description
                                                                                                                                                                    ""
                                                                                                                                                                  :> (Summary
                                                                                                                                                                        "Get config for mlsMigration"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            ('MissingPermission
                                                                                                                                                                               'Nothing)
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> ("teams"
                                                                                                                                                                                      :> (Capture
                                                                                                                                                                                            "tid"
                                                                                                                                                                                            TeamId
                                                                                                                                                                                          :> ("features"
                                                                                                                                                                                              :> ("mlsMigration"
                                                                                                                                                                                                  :> Get
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          MlsMigrationConfig))))))))))
                                                                                                                                                               :<|> (Named
                                                                                                                                                                       '("iput",
                                                                                                                                                                         MlsMigrationConfig)
                                                                                                                                                                       (Description
                                                                                                                                                                          ""
                                                                                                                                                                        :> (Summary
                                                                                                                                                                              "Put config for mlsMigration"
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  ('MissingPermission
                                                                                                                                                                                     'Nothing)
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              TeamFeatureError
                                                                                                                                                                                            :> (CanThrowMany
                                                                                                                                                                                                  '[]
                                                                                                                                                                                                :> ("teams"
                                                                                                                                                                                                    :> (Capture
                                                                                                                                                                                                          "tid"
                                                                                                                                                                                                          TeamId
                                                                                                                                                                                                        :> ("features"
                                                                                                                                                                                                            :> ("mlsMigration"
                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (Feature
                                                                                                                                                                                                                         MlsMigrationConfig)
                                                                                                                                                                                                                    :> Put
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                                                            MlsMigrationConfig)))))))))))))
                                                                                                                                                                     :<|> Named
                                                                                                                                                                            '("ipatch",
                                                                                                                                                                              MlsMigrationConfig)
                                                                                                                                                                            (Description
                                                                                                                                                                               ""
                                                                                                                                                                             :> (Summary
                                                                                                                                                                                   "Patch config for mlsMigration"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('MissingPermission
                                                                                                                                                                                          'Nothing)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   TeamFeatureError
                                                                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                                                                       '[]
                                                                                                                                                                                                     :> ("teams"
                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                               "tid"
                                                                                                                                                                                                               TeamId
                                                                                                                                                                                                             :> ("features"
                                                                                                                                                                                                                 :> ("mlsMigration"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                                                                              MlsMigrationConfig)
                                                                                                                                                                                                                         :> Patch
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                 MlsMigrationConfig)))))))))))))))
                                                                                                                                                              :<|> ((Named
                                                                                                                                                                       '("iget",
                                                                                                                                                                         EnforceFileDownloadLocationConfig)
                                                                                                                                                                       (Description
                                                                                                                                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                        :> (Summary
                                                                                                                                                                              "Get config for enforceFileDownloadLocation"
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  ('MissingPermission
                                                                                                                                                                                     'Nothing)
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                        :> ("teams"
                                                                                                                                                                                            :> (Capture
                                                                                                                                                                                                  "tid"
                                                                                                                                                                                                  TeamId
                                                                                                                                                                                                :> ("features"
                                                                                                                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                        :> Get
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                                                     :<|> (Named
                                                                                                                                                                             '("iput",
                                                                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                                                                             (Description
                                                                                                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                              :> (Summary
                                                                                                                                                                                    "Put config for enforceFileDownloadLocation"
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        ('MissingPermission
                                                                                                                                                                                           'Nothing)
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    TeamFeatureError
                                                                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                                                                        '[]
                                                                                                                                                                                                      :> ("teams"
                                                                                                                                                                                                          :> (Capture
                                                                                                                                                                                                                "tid"
                                                                                                                                                                                                                TeamId
                                                                                                                                                                                                              :> ("features"
                                                                                                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (Feature
                                                                                                                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                                          :> Put
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                                                                  EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                                                           :<|> Named
                                                                                                                                                                                  '("ipatch",
                                                                                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                                                                                  (Description
                                                                                                                                                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                                   :> (Summary
                                                                                                                                                                                         "Patch config for enforceFileDownloadLocation"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('MissingPermission
                                                                                                                                                                                                'Nothing)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         TeamFeatureError
                                                                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                                                                             '[]
                                                                                                                                                                                                           :> ("teams"
                                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                                     "tid"
                                                                                                                                                                                                                     TeamId
                                                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                                                       :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                                               :> Patch
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                       EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                                                    :<|> (Named
                                                                                                                                                                            '("iget",
                                                                                                                                                                              LimitedEventFanoutConfig)
                                                                                                                                                                            (Description
                                                                                                                                                                               ""
                                                                                                                                                                             :> (Summary
                                                                                                                                                                                   "Get config for limitedEventFanout"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('MissingPermission
                                                                                                                                                                                          'Nothing)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                       "tid"
                                                                                                                                                                                                       TeamId
                                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                                         :> ("limitedEventFanout"
                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     LimitedEventFanoutConfig))))))))))
                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                  '("iput",
                                                                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                                                                  (Description
                                                                                                                                                                                     ""
                                                                                                                                                                                   :> (Summary
                                                                                                                                                                                         "Put config for limitedEventFanout"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('MissingPermission
                                                                                                                                                                                                'Nothing)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         TeamFeatureError
                                                                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                                                                             '[]
                                                                                                                                                                                                           :> ("teams"
                                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                                     "tid"
                                                                                                                                                                                                                     TeamId
                                                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                                                       :> ("limitedEventFanout"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 (Feature
                                                                                                                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                                                                                                               :> Put
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                       LimitedEventFanoutConfig)))))))))))))
                                                                                                                                                                                :<|> Named
                                                                                                                                                                                       '("ipatch",
                                                                                                                                                                                         LimitedEventFanoutConfig)
                                                                                                                                                                                       (Description
                                                                                                                                                                                          ""
                                                                                                                                                                                        :> (Summary
                                                                                                                                                                                              "Patch config for limitedEventFanout"
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  ('MissingPermission
                                                                                                                                                                                                     'Nothing)
                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                              TeamFeatureError
                                                                                                                                                                                                            :> (CanThrowMany
                                                                                                                                                                                                                  '[]
                                                                                                                                                                                                                :> ("teams"
                                                                                                                                                                                                                    :> (Capture
                                                                                                                                                                                                                          "tid"
                                                                                                                                                                                                                          TeamId
                                                                                                                                                                                                                        :> ("features"
                                                                                                                                                                                                                            :> ("limitedEventFanout"
                                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      (LockableFeaturePatch
                                                                                                                                                                                                                                         LimitedEventFanoutConfig)
                                                                                                                                                                                                                                    :> Patch
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                                                                            LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                                                       :<|> (Named
                                                               '("ilock", FileSharingConfig)
                                                               (Summary "(Un-)lock fileSharing"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("fileSharing"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock",
                                                                       ConferenceCallingConfig)
                                                                     (Summary
                                                                        "(Un-)lock conferenceCalling"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("conferenceCalling"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock",
                                                                             SelfDeletingMessagesConfig)
                                                                           (Summary
                                                                              "(Un-)lock selfDeletingMessages"
                                                                            :> (Description ""
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("selfDeletingMessages"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("ilock",
                                                                                   GuestLinksConfig)
                                                                                 (Summary
                                                                                    "(Un-)lock conversationGuestLinks"
                                                                                  :> (Description ""
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("conversationGuestLinks"
                                                                                                              :> (Capture
                                                                                                                    "lockStatus"
                                                                                                                    LockStatus
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       LockStatusResponse)))))))))
                                                                               :<|> (Named
                                                                                       '("ilock",
                                                                                         SndFactorPasswordChallengeConfig)
                                                                                       (Summary
                                                                                          "(Un-)lock sndFactorPasswordChallenge"
                                                                                        :> (Description
                                                                                              ""
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("sndFactorPasswordChallenge"
                                                                                                                    :> (Capture
                                                                                                                          "lockStatus"
                                                                                                                          LockStatus
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             LockStatusResponse)))))))))
                                                                                     :<|> (Named
                                                                                             '("ilock",
                                                                                               MLSConfig)
                                                                                             (Summary
                                                                                                "(Un-)lock mls"
                                                                                              :> (Description
                                                                                                    ""
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mls"
                                                                                                                          :> (Capture
                                                                                                                                "lockStatus"
                                                                                                                                LockStatus
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   LockStatusResponse)))))))))
                                                                                           :<|> (Named
                                                                                                   '("ilock",
                                                                                                     OutlookCalIntegrationConfig)
                                                                                                   (Summary
                                                                                                      "(Un-)lock outlookCalIntegration"
                                                                                                    :> (Description
                                                                                                          ""
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("outlookCalIntegration"
                                                                                                                                :> (Capture
                                                                                                                                      "lockStatus"
                                                                                                                                      LockStatus
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         LockStatusResponse)))))))))
                                                                                                 :<|> (Named
                                                                                                         '("ilock",
                                                                                                           MlsE2EIdConfig)
                                                                                                         (Summary
                                                                                                            "(Un-)lock mlsE2EId"
                                                                                                          :> (Description
                                                                                                                ""
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("mlsE2EId"
                                                                                                                                      :> (Capture
                                                                                                                                            "lockStatus"
                                                                                                                                            LockStatus
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               LockStatusResponse)))))))))
                                                                                                       :<|> (Named
                                                                                                               '("ilock",
                                                                                                                 MlsMigrationConfig)
                                                                                                               (Summary
                                                                                                                  "(Un-)lock mlsMigration"
                                                                                                                :> (Description
                                                                                                                      ""
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("mlsMigration"
                                                                                                                                            :> (Capture
                                                                                                                                                  "lockStatus"
                                                                                                                                                  LockStatus
                                                                                                                                                :> Put
                                                                                                                                                     '[JSON]
                                                                                                                                                     LockStatusResponse)))))))))
                                                                                                             :<|> (Named
                                                                                                                     '("ilock",
                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                     (Summary
                                                                                                                        "(Un-)lock enforceFileDownloadLocation"
                                                                                                                      :> (Description
                                                                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "lockStatus"
                                                                                                                                                        LockStatus
                                                                                                                                                      :> Put
                                                                                                                                                           '[JSON]
                                                                                                                                                           LockStatusResponse)))))))))
                                                                                                                   :<|> (Named
                                                                                                                           '("igetmulti",
                                                                                                                             SearchVisibilityInboundConfig)
                                                                                                                           (Summary
                                                                                                                              "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                                                            :> ("features-multi-teams"
                                                                                                                                :> ("searchVisibilityInbound"
                                                                                                                                    :> (ReqBody
                                                                                                                                          '[JSON]
                                                                                                                                          TeamFeatureNoConfigMultiRequest
                                                                                                                                        :> Post
                                                                                                                                             '[JSON]
                                                                                                                                             (TeamFeatureNoConfigMultiResponse
                                                                                                                                                SearchVisibilityInboundConfig)))))
                                                                                                                         :<|> Named
                                                                                                                                "feature-configs-internal"
                                                                                                                                (Summary
                                                                                                                                   "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('MissingPermission
                                                                                                                                              'Nothing)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NotATeamMember
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'TeamNotFound
                                                                                                                                                 :> (QueryParam'
                                                                                                                                                       '[Optional,
                                                                                                                                                         Strict,
                                                                                                                                                         Description
                                                                                                                                                           "Optional user id"]
                                                                                                                                                       "user_id"
                                                                                                                                                       UserId
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          AllTeamFeatures))))))))))))))))))
                                                      :<|> (IFederationAPI
                                                            :<|> (IConversationAPI
                                                                  :<|> IEJPDAPI)))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"connect" (((HasAnnotation 'Remote "brig" "api-version",
  (HasAnnotation 'Remote "galley" "on-conversation-created",
   (HasAnnotation 'Remote "galley" "on-conversation-updated",
    () :: Constraint))) =>
 QualifiedWithTag 'QLocal UserId
 -> Maybe ConnId
 -> Connect
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()),
        Error (Tagged 'NotConnected ()), 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]
      (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
-> Connect
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NotConnected ()), 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]
     (ResponseForExistedCreated Conversation)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> Maybe ConnId
 -> Connect
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()),
        Error (Tagged 'NotConnected ()), 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]
      (ResponseForExistedCreated Conversation))
-> QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> Connect
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NotConnected ()), 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]
     (ResponseForExistedCreated Conversation)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> Connect
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NotConnected ()), 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]
     (ResponseForExistedCreated Conversation)
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> Connect
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NotConnected ()), 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]
     (ConversationResponse Conversation)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r,
 Member ConversationStore r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error FederationError) r, Member (Error InternalError) r,
 Member (Error InvalidInput) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member (Error UnreachableBackends) r, Member FederatorAccess r,
 Member NotificationSubsystem r, Member (Input UTCTime) r,
 Member MemberStore r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> Connect
-> Sem r (ConversationResponse Conversation)
Create.createConnectConversation))
      API
  (Named
     "connect"
     (Summary "Create a connect conversation (deprecated)"
      :> (MakesFederatedCall 'Brig "api-version"
          :> (MakesFederatedCall 'Galley "on-conversation-created"
              :> (MakesFederatedCall 'Galley "on-conversation-updated"
                  :> (CanThrow 'ConvNotFound
                      :> (CanThrow 'InvalidOperation
                          :> (CanThrow 'NotConnected
                              :> (CanThrow UnreachableBackends
                                  :> (ZLocalUser
                                      :> (ZOptConn
                                          :> ("conversations"
                                              :> ("connect"
                                                  :> (ReqBody '[JSON] Connect
                                                      :> 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-conversation-clients"
        (Summary "Get mls conversation client list"
         :> (CanThrow 'ConvNotFound
             :> ("group"
                 :> (Capture "gid" GroupId
                     :> MultiVerb
                          'GET '[JSON] '[Respond 200 "Clients" ClientList] ClientList))))
      :<|> (Named
              "guard-legalhold-policy-conflicts"
              ("guard-legalhold-policy-conflicts"
               :> (CanThrow 'MissingLegalholdConsent
                   :> (CanThrow 'MissingLegalholdConsentOldClients
                       :> (ReqBody '[JSON] GuardLegalholdPolicyConflicts
                           :> MultiVerb
                                'PUT '[JSON] '[RespondEmpty 200 "Guard Legalhold Policy"] ()))))
            :<|> (("legalhold"
                   :> ("whitelisted-teams"
                       :> (Capture "tid" TeamId
                           :> (Named
                                 "set-team-legalhold-whitelisted"
                                 (MultiVerb
                                    'PUT
                                    '[JSON]
                                    '[RespondEmpty 200 "Team Legalhold Whitelisted"]
                                    ())
                               :<|> (Named
                                       "unset-team-legalhold-whitelisted"
                                       (MultiVerb
                                          'DELETE
                                          '[JSON]
                                          '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
                                          ())
                                     :<|> Named
                                            "get-team-legalhold-whitelisted"
                                            (MultiVerb
                                               'GET
                                               '[JSON]
                                               '[RespondEmpty 404 "Team not Legalhold Whitelisted",
                                                 RespondEmpty 200 "Team Legalhold Whitelisted"]
                                               Bool))))))
                  :<|> (("teams"
                         :> (Capture "tid" TeamId
                             :> (Named
                                   "get-team-internal"
                                   (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
                                 :<|> (Named
                                         "create-binding-team"
                                         (ZUser
                                          :> (ReqBody '[JSON] BindingNewTeam
                                              :> MultiVerb
                                                   'PUT
                                                   '[JSON]
                                                   '[WithHeaders
                                                       '[Header "Location" TeamId]
                                                       TeamId
                                                       (RespondEmpty 201 "OK")]
                                                   TeamId))
                                       :<|> (Named
                                               "delete-binding-team"
                                               (CanThrow 'NoBindingTeam
                                                :> (CanThrow 'NotAOneMemberTeam
                                                    :> (CanThrow 'DeleteQueueFull
                                                        :> (CanThrow 'TeamNotFound
                                                            :> (QueryFlag "force"
                                                                :> MultiVerb
                                                                     'DELETE
                                                                     '[JSON]
                                                                     '[RespondEmpty 202 "OK"]
                                                                     ())))))
                                             :<|> (Named
                                                     "get-team-name"
                                                     ("name"
                                                      :> (CanThrow 'TeamNotFound
                                                          :> Get '[JSON] TeamName))
                                                   :<|> (Named
                                                           "update-team-status"
                                                           ("status"
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow
                                                                      'InvalidTeamStatusUpdate
                                                                    :> (ReqBody
                                                                          '[JSON] TeamStatusUpdate
                                                                        :> MultiVerb
                                                                             'PUT
                                                                             '[JSON]
                                                                             '[RespondEmpty
                                                                                 200 "OK"]
                                                                             ()))))
                                                         :<|> (("members"
                                                                :> (Named
                                                                      "unchecked-add-team-member"
                                                                      (CanThrow 'TooManyTeamMembers
                                                                       :> (CanThrow
                                                                             'TooManyTeamMembersOnTeamWithLegalhold
                                                                           :> (CanThrow
                                                                                 'TooManyTeamAdmins
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     NewTeamMember
                                                                                   :> MultiVerb
                                                                                        'POST
                                                                                        '[JSON]
                                                                                        '[RespondEmpty
                                                                                            200
                                                                                            "OK"]
                                                                                        ()))))
                                                                    :<|> (Named
                                                                            "unchecked-get-team-members"
                                                                            (QueryParam'
                                                                               '[Strict]
                                                                               "maxResults"
                                                                               (Range
                                                                                  1
                                                                                  HardTruncationLimit
                                                                                  Int32)
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  TeamMemberList)
                                                                          :<|> (Named
                                                                                  "unchecked-get-team-member"
                                                                                  (Capture
                                                                                     "uid" UserId
                                                                                   :> (CanThrow
                                                                                         'TeamMemberNotFound
                                                                                       :> Get
                                                                                            '[JSON]
                                                                                            TeamMember))
                                                                                :<|> (Named
                                                                                        "can-user-join-team"
                                                                                        ("check"
                                                                                         :> (CanThrow
                                                                                               'TooManyTeamMembersOnTeamWithLegalhold
                                                                                             :> MultiVerb
                                                                                                  'GET
                                                                                                  '[JSON]
                                                                                                  '[RespondEmpty
                                                                                                      200
                                                                                                      "User can join"]
                                                                                                  ()))
                                                                                      :<|> Named
                                                                                             "unchecked-update-team-member"
                                                                                             (CanThrow
                                                                                                'AccessDenied
                                                                                              :> (CanThrow
                                                                                                    'InvalidPermissions
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> (CanThrow
                                                                                                            'TeamMemberNotFound
                                                                                                          :> (CanThrow
                                                                                                                'TooManyTeamAdmins
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        ('MissingPermission
                                                                                                                           'Nothing)
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            NewTeamMember
                                                                                                                          :> MultiVerb
                                                                                                                               'PUT
                                                                                                                               '[JSON]
                                                                                                                               '[RespondEmpty
                                                                                                                                   200
                                                                                                                                   ""]
                                                                                                                               ())))))))))))))
                                                               :<|> (Named
                                                                       "user-is-team-owner"
                                                                       ("is-team-owner"
                                                                        :> (Capture "uid" UserId
                                                                            :> (CanThrow
                                                                                  'AccessDenied
                                                                                :> (CanThrow
                                                                                      'TeamMemberNotFound
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> MultiVerb
                                                                                             'GET
                                                                                             '[JSON]
                                                                                             '[RespondEmpty
                                                                                                 200
                                                                                                 "User is team owner"]
                                                                                             ())))))
                                                                     :<|> ("search-visibility"
                                                                           :> (Named
                                                                                 "get-search-visibility-internal"
                                                                                 (Get
                                                                                    '[JSON]
                                                                                    TeamSearchVisibilityView)
                                                                               :<|> Named
                                                                                      "set-search-visibility-internal"
                                                                                      (CanThrow
                                                                                         'TeamSearchVisibilityNotEnabled
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         TeamSearchVisibilityView
                                                                                                       :> MultiVerb
                                                                                                            'PUT
                                                                                                            '[JSON]
                                                                                                            '[RespondEmpty
                                                                                                                204
                                                                                                                "OK"]
                                                                                                            ()))))))))))))))))
                        :<|> ((Named
                                 "get-team-members"
                                 (CanThrow 'NonBindingTeam
                                  :> (CanThrow 'TeamNotFound
                                      :> ("users"
                                          :> (Capture "uid" UserId
                                              :> ("team"
                                                  :> ("members" :> Get '[JSON] TeamMemberList))))))
                               :<|> (Named
                                       "get-team-id"
                                       (CanThrow 'NonBindingTeam
                                        :> (CanThrow 'TeamNotFound
                                            :> ("users"
                                                :> (Capture "uid" UserId
                                                    :> ("team" :> Get '[JSON] TeamId)))))
                                     :<|> (Named
                                             "test-get-clients"
                                             ("test"
                                              :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
                                           :<|> (Named
                                                   "test-add-client"
                                                   ("clients"
                                                    :> (ZUser
                                                        :> (Capture "cid" ClientId
                                                            :> MultiVerb
                                                                 'POST
                                                                 '[JSON]
                                                                 '[RespondEmpty 200 "OK"]
                                                                 ())))
                                                 :<|> (Named
                                                         "test-delete-client"
                                                         ("clients"
                                                          :> (ZUser
                                                              :> (Capture "cid" ClientId
                                                                  :> MultiVerb
                                                                       'DELETE
                                                                       '[JSON]
                                                                       '[RespondEmpty 200 "OK"]
                                                                       ())))
                                                       :<|> (Named
                                                               "add-service"
                                                               ("services"
                                                                :> (ReqBody '[JSON] Service
                                                                    :> MultiVerb
                                                                         'POST
                                                                         '[JSON]
                                                                         '[RespondEmpty 200 "OK"]
                                                                         ()))
                                                             :<|> (Named
                                                                     "delete-service"
                                                                     ("services"
                                                                      :> (ReqBody '[JSON] ServiceRef
                                                                          :> MultiVerb
                                                                               'DELETE
                                                                               '[JSON]
                                                                               '[RespondEmpty
                                                                                   200 "OK"]
                                                                               ()))
                                                                   :<|> (Named
                                                                           "i-add-bot"
                                                                           (CanThrow
                                                                              ('ActionDenied
                                                                                 'AddConversationMember)
                                                                            :> (CanThrow
                                                                                  'ConvNotFound
                                                                                :> (CanThrow
                                                                                      'InvalidOperation
                                                                                    :> (CanThrow
                                                                                          'TooManyMembers
                                                                                        :> ("bots"
                                                                                            :> (ZLocalUser
                                                                                                :> (ZConn
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          AddBot
                                                                                                        :> Post
                                                                                                             '[JSON]
                                                                                                             Event))))))))
                                                                         :<|> (Named
                                                                                 "delete-bot"
                                                                                 (CanThrow
                                                                                    'ConvNotFound
                                                                                  :> (CanThrow
                                                                                        ('ActionDenied
                                                                                           'RemoveConversationMember)
                                                                                      :> ("bots"
                                                                                          :> (ZLocalUser
                                                                                              :> (ZOptConn
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        RemoveBot
                                                                                                      :> MultiVerb
                                                                                                           'DELETE
                                                                                                           '[JSON]
                                                                                                           (UpdateResponses
                                                                                                              "Bot not found"
                                                                                                              "Bot deleted"
                                                                                                              Event)
                                                                                                           (UpdateResult
                                                                                                              Event)))))))
                                                                               :<|> (Named
                                                                                       "put-custom-backend"
                                                                                       ("custom-backend"
                                                                                        :> ("by-domain"
                                                                                            :> (Capture
                                                                                                  "domain"
                                                                                                  Domain
                                                                                                :> (ReqBody
                                                                                                      '[JSON]
                                                                                                      CustomBackend
                                                                                                    :> MultiVerb
                                                                                                         'PUT
                                                                                                         '[JSON]
                                                                                                         '[RespondEmpty
                                                                                                             201
                                                                                                             "OK"]
                                                                                                         ()))))
                                                                                     :<|> Named
                                                                                            "delete-custom-backend"
                                                                                            ("custom-backend"
                                                                                             :> ("by-domain"
                                                                                                 :> (Capture
                                                                                                       "domain"
                                                                                                       Domain
                                                                                                     :> MultiVerb
                                                                                                          'DELETE
                                                                                                          '[JSON]
                                                                                                          '[RespondEmpty
                                                                                                              200
                                                                                                              "OK"]
                                                                                                          ())))))))))))))
                              :<|> (Named
                                      "upsert-one2one"
                                      (Summary "Create or Update a connect or one2one conversation."
                                       :> ("conversations"
                                           :> ("one2one"
                                               :> ("upsert"
                                                   :> (ReqBody
                                                         '[JSON] UpsertOne2OneConversationRequest
                                                       :> MultiVerb
                                                            'POST
                                                            '[JSON]
                                                            '[RespondEmpty
                                                                200 "Upsert One2One Policy"]
                                                            ())))))
                                    :<|> ((((Named
                                               '("iget", LegalholdConfig)
                                               (Description ""
                                                :> (Summary "Get config for legalhold"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("legalhold"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        LegalholdConfig))))))))))
                                             :<|> (Named
                                                     '("iput", LegalholdConfig)
                                                     (Description ""
                                                      :> (Summary "Put config for legalhold"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany
                                                                                '[ 'ActionDenied
                                                                                     'RemoveConversationMember,
                                                                                   'CannotEnableLegalHoldServiceLargeTeam,
                                                                                   'LegalHoldNotEnabled,
                                                                                   'LegalHoldDisableUnimplemented,
                                                                                   'LegalHoldServiceNotRegistered,
                                                                                   'UserLegalHoldIllegalOperation,
                                                                                   'LegalHoldCouldNotBlockConnections]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("legalhold"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (Feature
                                                                                                       LegalholdConfig)
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          LegalholdConfig)))))))))))))
                                                   :<|> Named
                                                          '("ipatch", LegalholdConfig)
                                                          (Description ""
                                                           :> (Summary "Patch config for legalhold"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany
                                                                                     '[ 'ActionDenied
                                                                                          'RemoveConversationMember,
                                                                                        'CannotEnableLegalHoldServiceLargeTeam,
                                                                                        'LegalHoldNotEnabled,
                                                                                        'LegalHoldDisableUnimplemented,
                                                                                        'LegalHoldServiceNotRegistered,
                                                                                        'UserLegalHoldIllegalOperation,
                                                                                        'LegalHoldCouldNotBlockConnections]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("legalhold"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (LockableFeaturePatch
                                                                                                            LegalholdConfig)
                                                                                                       :> Patch
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               LegalholdConfig)))))))))))))))
                                            :<|> ((Named
                                                     '("iget", SSOConfig)
                                                     (Description ""
                                                      :> (Summary "Get config for sso"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("sso"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              SSOConfig))))))))))
                                                   :<|> (Named
                                                           '("iput", SSOConfig)
                                                           (Description ""
                                                            :> (Summary "Put config for sso"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("sso"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             SSOConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SSOConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch", SSOConfig)
                                                                (Description ""
                                                                 :> (Summary "Patch config for sso"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("sso"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  SSOConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     SSOConfig)))))))))))))))
                                                  :<|> ((Named
                                                           '("iget",
                                                             SearchVisibilityAvailableConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Get config for searchVisibility"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("searchVisibility"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    SearchVisibilityAvailableConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput",
                                                                   SearchVisibilityAvailableConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Put config for searchVisibility"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("searchVisibility"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   SearchVisibilityAvailableConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      SearchVisibilityAvailableConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch",
                                                                        SearchVisibilityAvailableConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for searchVisibility"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("searchVisibility"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        SearchVisibilityAvailableConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           SearchVisibilityAvailableConfig)))))))))))))))
                                                        :<|> ((Named
                                                                 '("iget",
                                                                   SearchVisibilityInboundConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Get config for searchVisibilityInbound"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("searchVisibilityInbound"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          SearchVisibilityInboundConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput",
                                                                         SearchVisibilityInboundConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for searchVisibilityInbound"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("searchVisibilityInbound"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         SearchVisibilityInboundConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            SearchVisibilityInboundConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch",
                                                                              SearchVisibilityInboundConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for searchVisibilityInbound"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("searchVisibilityInbound"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              SearchVisibilityInboundConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 SearchVisibilityInboundConfig)))))))))))))))
                                                              :<|> ((Named
                                                                       '("iget",
                                                                         ValidateSAMLEmailsConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for validateSAMLemails"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("validateSAMLemails"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                ValidateSAMLEmailsConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               ValidateSAMLEmailsConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for validateSAMLemails"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("validateSAMLemails"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               ValidateSAMLEmailsConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  ValidateSAMLEmailsConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    ValidateSAMLEmailsConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for validateSAMLemails"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("validateSAMLemails"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    ValidateSAMLEmailsConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       ValidateSAMLEmailsConfig)))))))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               DigitalSignaturesConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for digitalSignatures"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("digitalSignatures"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      DigitalSignaturesConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     DigitalSignaturesConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for digitalSignatures"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("digitalSignatures"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     DigitalSignaturesConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        DigitalSignaturesConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          DigitalSignaturesConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for digitalSignatures"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("digitalSignatures"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          DigitalSignaturesConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             DigitalSignaturesConfig)))))))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     AppLockConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for appLock"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("appLock"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            AppLockConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           AppLockConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for appLock"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("appLock"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           AppLockConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              AppLockConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                AppLockConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for appLock"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("appLock"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                AppLockConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   AppLockConfig)))))))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           FileSharingConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for fileSharing"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("fileSharing"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  FileSharingConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 FileSharingConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for fileSharing"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("fileSharing"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 FileSharingConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    FileSharingConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      FileSharingConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for fileSharing"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("fileSharing"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      FileSharingConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         FileSharingConfig)))))))))))))))
                                                                                      :<|> (Named
                                                                                              '("iget",
                                                                                                ClassifiedDomainsConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Get config for classifiedDomains"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("classifiedDomains"
                                                                                                                               :> Get
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       ClassifiedDomainsConfig))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       ConferenceCallingConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for conferenceCalling"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("conferenceCalling"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              ConferenceCallingConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             ConferenceCallingConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for conferenceCalling"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("conferenceCalling"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             ConferenceCallingConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                ConferenceCallingConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  ConferenceCallingConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for conferenceCalling"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("conferenceCalling"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  ConferenceCallingConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     ConferenceCallingConfig)))))))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             SelfDeletingMessagesConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for selfDeletingMessages"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("selfDeletingMessages"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    SelfDeletingMessagesConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   SelfDeletingMessagesConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for selfDeletingMessages"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("selfDeletingMessages"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   SelfDeletingMessagesConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      SelfDeletingMessagesConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        SelfDeletingMessagesConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for selfDeletingMessages"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("selfDeletingMessages"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        SelfDeletingMessagesConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           SelfDeletingMessagesConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   GuestLinksConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for conversationGuestLinks"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("conversationGuestLinks"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          GuestLinksConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         GuestLinksConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for conversationGuestLinks"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("conversationGuestLinks"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         GuestLinksConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            GuestLinksConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              GuestLinksConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for conversationGuestLinks"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              GuestLinksConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 GuestLinksConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         SndFactorPasswordChallengeConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for sndFactorPasswordChallenge"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("sndFactorPasswordChallenge"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                SndFactorPasswordChallengeConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               SndFactorPasswordChallengeConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for sndFactorPasswordChallenge"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("sndFactorPasswordChallenge"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               SndFactorPasswordChallengeConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  SndFactorPasswordChallengeConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    SndFactorPasswordChallengeConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for sndFactorPasswordChallenge"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    SndFactorPasswordChallengeConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               MLSConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for mls"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("mls"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      MLSConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     MLSConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for mls"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("mls"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     MLSConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        MLSConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          MLSConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for mls"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("mls"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          MLSConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             MLSConfig)))))))))))))))
                                                                                                                          :<|> ((Named
                                                                                                                                   '("iget",
                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                                                 :<|> (Named
                                                                                                                                         '("iput",
                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Feature
                                                                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                      :> Put
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                                                       :<|> Named
                                                                                                                                              '("ipatch",
                                                                                                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                                                :<|> ((Named
                                                                                                                                         '("iget",
                                                                                                                                           OutlookCalIntegrationConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for outlookCalIntegration"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("outlookCalIntegration"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  OutlookCalIntegrationConfig))))))))))
                                                                                                                                       :<|> (Named
                                                                                                                                               '("iput",
                                                                                                                                                 OutlookCalIntegrationConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Put config for outlookCalIntegration"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                          '[]
                                                                                                                                                                        :> ("teams"
                                                                                                                                                                            :> (Capture
                                                                                                                                                                                  "tid"
                                                                                                                                                                                  TeamId
                                                                                                                                                                                :> ("features"
                                                                                                                                                                                    :> ("outlookCalIntegration"
                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (Feature
                                                                                                                                                                                                 OutlookCalIntegrationConfig)
                                                                                                                                                                                            :> Put
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    OutlookCalIntegrationConfig)))))))))))))
                                                                                                                                             :<|> Named
                                                                                                                                                    '("ipatch",
                                                                                                                                                      OutlookCalIntegrationConfig)
                                                                                                                                                    (Description
                                                                                                                                                       ""
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Patch config for outlookCalIntegration"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("outlookCalIntegration"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                                                      OutlookCalIntegrationConfig)
                                                                                                                                                                                                 :> Patch
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         OutlookCalIntegrationConfig)))))))))))))))
                                                                                                                                      :<|> ((Named
                                                                                                                                               '("iget",
                                                                                                                                                 MlsE2EIdConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Get config for mlsE2EId"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("mlsE2EId"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        MlsE2EIdConfig))))))))))
                                                                                                                                             :<|> (Named
                                                                                                                                                     '("iput",
                                                                                                                                                       MlsE2EIdConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Put config for mlsE2EId"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                          :> (CanThrowMany
                                                                                                                                                                                '[]
                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                        "tid"
                                                                                                                                                                                        TeamId
                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                          :> ("mlsE2EId"
                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (Feature
                                                                                                                                                                                                       MlsE2EIdConfig)
                                                                                                                                                                                                  :> Put
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          MlsE2EIdConfig)))))))))))))
                                                                                                                                                   :<|> Named
                                                                                                                                                          '("ipatch",
                                                                                                                                                            MlsE2EIdConfig)
                                                                                                                                                          (Description
                                                                                                                                                             ""
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Patch config for mlsE2EId"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('MissingPermission
                                                                                                                                                                        'Nothing)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 TeamFeatureError
                                                                                                                                                                               :> (CanThrowMany
                                                                                                                                                                                     '[]
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> ("mlsE2EId"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                                                                            MlsE2EIdConfig)
                                                                                                                                                                                                       :> Patch
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               MlsE2EIdConfig)))))))))))))))
                                                                                                                                            :<|> ((Named
                                                                                                                                                     '("iget",
                                                                                                                                                       MlsMigrationConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Get config for mlsMigration"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("mlsMigration"
                                                                                                                                                                                      :> Get
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              MlsMigrationConfig))))))))))
                                                                                                                                                   :<|> (Named
                                                                                                                                                           '("iput",
                                                                                                                                                             MlsMigrationConfig)
                                                                                                                                                           (Description
                                                                                                                                                              ""
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Put config for mlsMigration"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  TeamFeatureError
                                                                                                                                                                                :> (CanThrowMany
                                                                                                                                                                                      '[]
                                                                                                                                                                                    :> ("teams"
                                                                                                                                                                                        :> (Capture
                                                                                                                                                                                              "tid"
                                                                                                                                                                                              TeamId
                                                                                                                                                                                            :> ("features"
                                                                                                                                                                                                :> ("mlsMigration"
                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (Feature
                                                                                                                                                                                                             MlsMigrationConfig)
                                                                                                                                                                                                        :> Put
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                MlsMigrationConfig)))))))))))))
                                                                                                                                                         :<|> Named
                                                                                                                                                                '("ipatch",
                                                                                                                                                                  MlsMigrationConfig)
                                                                                                                                                                (Description
                                                                                                                                                                   ""
                                                                                                                                                                 :> (Summary
                                                                                                                                                                       "Patch config for mlsMigration"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('MissingPermission
                                                                                                                                                                              'Nothing)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       TeamFeatureError
                                                                                                                                                                                     :> (CanThrowMany
                                                                                                                                                                                           '[]
                                                                                                                                                                                         :> ("teams"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "tid"
                                                                                                                                                                                                   TeamId
                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                     :> ("mlsMigration"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                                                                  MlsMigrationConfig)
                                                                                                                                                                                                             :> Patch
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     MlsMigrationConfig)))))))))))))))
                                                                                                                                                  :<|> ((Named
                                                                                                                                                           '("iget",
                                                                                                                                                             EnforceFileDownloadLocationConfig)
                                                                                                                                                           (Description
                                                                                                                                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Get config for enforceFileDownloadLocation"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                :> (Capture
                                                                                                                                                                                      "tid"
                                                                                                                                                                                      TeamId
                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                        :> ("enforceFileDownloadLocation"
                                                                                                                                                                                            :> Get
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                                         :<|> (Named
                                                                                                                                                                 '("iput",
                                                                                                                                                                   EnforceFileDownloadLocationConfig)
                                                                                                                                                                 (Description
                                                                                                                                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                  :> (Summary
                                                                                                                                                                        "Put config for enforceFileDownloadLocation"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            ('MissingPermission
                                                                                                                                                                               'Nothing)
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        TeamFeatureError
                                                                                                                                                                                      :> (CanThrowMany
                                                                                                                                                                                            '[]
                                                                                                                                                                                          :> ("teams"
                                                                                                                                                                                              :> (Capture
                                                                                                                                                                                                    "tid"
                                                                                                                                                                                                    TeamId
                                                                                                                                                                                                  :> ("features"
                                                                                                                                                                                                      :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (Feature
                                                                                                                                                                                                                   EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                              :> Put
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                                      EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                                               :<|> Named
                                                                                                                                                                      '("ipatch",
                                                                                                                                                                        EnforceFileDownloadLocationConfig)
                                                                                                                                                                      (Description
                                                                                                                                                                         "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                       :> (Summary
                                                                                                                                                                             "Patch config for enforceFileDownloadLocation"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('MissingPermission
                                                                                                                                                                                    'Nothing)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             TeamFeatureError
                                                                                                                                                                                           :> (CanThrowMany
                                                                                                                                                                                                 '[]
                                                                                                                                                                                               :> ("teams"
                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                         "tid"
                                                                                                                                                                                                         TeamId
                                                                                                                                                                                                       :> ("features"
                                                                                                                                                                                                           :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                                                                        EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                                   :> Patch
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                           EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                                        :<|> (Named
                                                                                                                                                                '("iget",
                                                                                                                                                                  LimitedEventFanoutConfig)
                                                                                                                                                                (Description
                                                                                                                                                                   ""
                                                                                                                                                                 :> (Summary
                                                                                                                                                                       "Get config for limitedEventFanout"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('MissingPermission
                                                                                                                                                                              'Nothing)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("teams"
                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                           "tid"
                                                                                                                                                                                           TeamId
                                                                                                                                                                                         :> ("features"
                                                                                                                                                                                             :> ("limitedEventFanout"
                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         LimitedEventFanoutConfig))))))))))
                                                                                                                                                              :<|> (Named
                                                                                                                                                                      '("iput",
                                                                                                                                                                        LimitedEventFanoutConfig)
                                                                                                                                                                      (Description
                                                                                                                                                                         ""
                                                                                                                                                                       :> (Summary
                                                                                                                                                                             "Put config for limitedEventFanout"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('MissingPermission
                                                                                                                                                                                    'Nothing)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             TeamFeatureError
                                                                                                                                                                                           :> (CanThrowMany
                                                                                                                                                                                                 '[]
                                                                                                                                                                                               :> ("teams"
                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                         "tid"
                                                                                                                                                                                                         TeamId
                                                                                                                                                                                                       :> ("features"
                                                                                                                                                                                                           :> ("limitedEventFanout"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     (Feature
                                                                                                                                                                                                                        LimitedEventFanoutConfig)
                                                                                                                                                                                                                   :> Put
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                           LimitedEventFanoutConfig)))))))))))))
                                                                                                                                                                    :<|> Named
                                                                                                                                                                           '("ipatch",
                                                                                                                                                                             LimitedEventFanoutConfig)
                                                                                                                                                                           (Description
                                                                                                                                                                              ""
                                                                                                                                                                            :> (Summary
                                                                                                                                                                                  "Patch config for limitedEventFanout"
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                                         'Nothing)
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  TeamFeatureError
                                                                                                                                                                                                :> (CanThrowMany
                                                                                                                                                                                                      '[]
                                                                                                                                                                                                    :> ("teams"
                                                                                                                                                                                                        :> (Capture
                                                                                                                                                                                                              "tid"
                                                                                                                                                                                                              TeamId
                                                                                                                                                                                                            :> ("features"
                                                                                                                                                                                                                :> ("limitedEventFanout"
                                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          (LockableFeaturePatch
                                                                                                                                                                                                                             LimitedEventFanoutConfig)
                                                                                                                                                                                                                        :> Patch
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                                LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                                           :<|> (Named
                                                   '("ilock", FileSharingConfig)
                                                   (Summary "(Un-)lock fileSharing"
                                                    :> (Description ""
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("fileSharing"
                                                                                :> (Capture
                                                                                      "lockStatus"
                                                                                      LockStatus
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         LockStatusResponse)))))))))
                                                 :<|> (Named
                                                         '("ilock", ConferenceCallingConfig)
                                                         (Summary "(Un-)lock conferenceCalling"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("conferenceCalling"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock",
                                                                 SelfDeletingMessagesConfig)
                                                               (Summary
                                                                  "(Un-)lock selfDeletingMessages"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("selfDeletingMessages"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock", GuestLinksConfig)
                                                                     (Summary
                                                                        "(Un-)lock conversationGuestLinks"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("conversationGuestLinks"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock",
                                                                             SndFactorPasswordChallengeConfig)
                                                                           (Summary
                                                                              "(Un-)lock sndFactorPasswordChallenge"
                                                                            :> (Description ""
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("sndFactorPasswordChallenge"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("ilock",
                                                                                   MLSConfig)
                                                                                 (Summary
                                                                                    "(Un-)lock mls"
                                                                                  :> (Description ""
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mls"
                                                                                                              :> (Capture
                                                                                                                    "lockStatus"
                                                                                                                    LockStatus
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       LockStatusResponse)))))))))
                                                                               :<|> (Named
                                                                                       '("ilock",
                                                                                         OutlookCalIntegrationConfig)
                                                                                       (Summary
                                                                                          "(Un-)lock outlookCalIntegration"
                                                                                        :> (Description
                                                                                              ""
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("outlookCalIntegration"
                                                                                                                    :> (Capture
                                                                                                                          "lockStatus"
                                                                                                                          LockStatus
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             LockStatusResponse)))))))))
                                                                                     :<|> (Named
                                                                                             '("ilock",
                                                                                               MlsE2EIdConfig)
                                                                                             (Summary
                                                                                                "(Un-)lock mlsE2EId"
                                                                                              :> (Description
                                                                                                    ""
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mlsE2EId"
                                                                                                                          :> (Capture
                                                                                                                                "lockStatus"
                                                                                                                                LockStatus
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   LockStatusResponse)))))))))
                                                                                           :<|> (Named
                                                                                                   '("ilock",
                                                                                                     MlsMigrationConfig)
                                                                                                   (Summary
                                                                                                      "(Un-)lock mlsMigration"
                                                                                                    :> (Description
                                                                                                          ""
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mlsMigration"
                                                                                                                                :> (Capture
                                                                                                                                      "lockStatus"
                                                                                                                                      LockStatus
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         LockStatusResponse)))))))))
                                                                                                 :<|> (Named
                                                                                                         '("ilock",
                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                         (Summary
                                                                                                            "(Un-)lock enforceFileDownloadLocation"
                                                                                                          :> (Description
                                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                      :> (Capture
                                                                                                                                            "lockStatus"
                                                                                                                                            LockStatus
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               LockStatusResponse)))))))))
                                                                                                       :<|> (Named
                                                                                                               '("igetmulti",
                                                                                                                 SearchVisibilityInboundConfig)
                                                                                                               (Summary
                                                                                                                  "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                                                :> ("features-multi-teams"
                                                                                                                    :> ("searchVisibilityInbound"
                                                                                                                        :> (ReqBody
                                                                                                                              '[JSON]
                                                                                                                              TeamFeatureNoConfigMultiRequest
                                                                                                                            :> Post
                                                                                                                                 '[JSON]
                                                                                                                                 (TeamFeatureNoConfigMultiResponse
                                                                                                                                    SearchVisibilityInboundConfig)))))
                                                                                                             :<|> Named
                                                                                                                    "feature-configs-internal"
                                                                                                                    (Summary
                                                                                                                       "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> (CanThrow
                                                                                                                               ('MissingPermission
                                                                                                                                  'Nothing)
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotATeamMember
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TeamNotFound
                                                                                                                                     :> (QueryParam'
                                                                                                                                           '[Optional,
                                                                                                                                             Strict,
                                                                                                                                             Description
                                                                                                                                               "Optional user id"]
                                                                                                                                           "user_id"
                                                                                                                                           UserId
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              AllTeamFeatures))))))))))))))))))
                                          :<|> (IFederationAPI
                                                :<|> (IConversationAPI :<|> IEJPDAPI)))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "connect"
        (Summary "Create a connect conversation (deprecated)"
         :> (MakesFederatedCall 'Brig "api-version"
             :> (MakesFederatedCall 'Galley "on-conversation-created"
                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'InvalidOperation
                             :> (CanThrow 'NotConnected
                                 :> (CanThrow UnreachableBackends
                                     :> (ZLocalUser
                                         :> (ZOptConn
                                             :> ("conversations"
                                                 :> ("connect"
                                                     :> (ReqBody '[JSON] Connect
                                                         :> 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-conversation-clients"
              (Summary "Get mls conversation client list"
               :> (CanThrow 'ConvNotFound
                   :> ("group"
                       :> (Capture "gid" GroupId
                           :> MultiVerb
                                'GET '[JSON] '[Respond 200 "Clients" ClientList] ClientList))))
            :<|> (Named
                    "guard-legalhold-policy-conflicts"
                    ("guard-legalhold-policy-conflicts"
                     :> (CanThrow 'MissingLegalholdConsent
                         :> (CanThrow 'MissingLegalholdConsentOldClients
                             :> (ReqBody '[JSON] GuardLegalholdPolicyConflicts
                                 :> MultiVerb
                                      'PUT
                                      '[JSON]
                                      '[RespondEmpty 200 "Guard Legalhold Policy"]
                                      ()))))
                  :<|> (("legalhold"
                         :> ("whitelisted-teams"
                             :> (Capture "tid" TeamId
                                 :> (Named
                                       "set-team-legalhold-whitelisted"
                                       (MultiVerb
                                          'PUT
                                          '[JSON]
                                          '[RespondEmpty 200 "Team Legalhold Whitelisted"]
                                          ())
                                     :<|> (Named
                                             "unset-team-legalhold-whitelisted"
                                             (MultiVerb
                                                'DELETE
                                                '[JSON]
                                                '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
                                                ())
                                           :<|> Named
                                                  "get-team-legalhold-whitelisted"
                                                  (MultiVerb
                                                     'GET
                                                     '[JSON]
                                                     '[RespondEmpty
                                                         404 "Team not Legalhold Whitelisted",
                                                       RespondEmpty
                                                         200 "Team Legalhold Whitelisted"]
                                                     Bool))))))
                        :<|> (("teams"
                               :> (Capture "tid" TeamId
                                   :> (Named
                                         "get-team-internal"
                                         (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
                                       :<|> (Named
                                               "create-binding-team"
                                               (ZUser
                                                :> (ReqBody '[JSON] BindingNewTeam
                                                    :> MultiVerb
                                                         'PUT
                                                         '[JSON]
                                                         '[WithHeaders
                                                             '[Header "Location" TeamId]
                                                             TeamId
                                                             (RespondEmpty 201 "OK")]
                                                         TeamId))
                                             :<|> (Named
                                                     "delete-binding-team"
                                                     (CanThrow 'NoBindingTeam
                                                      :> (CanThrow 'NotAOneMemberTeam
                                                          :> (CanThrow 'DeleteQueueFull
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> (QueryFlag "force"
                                                                      :> MultiVerb
                                                                           'DELETE
                                                                           '[JSON]
                                                                           '[RespondEmpty 202 "OK"]
                                                                           ())))))
                                                   :<|> (Named
                                                           "get-team-name"
                                                           ("name"
                                                            :> (CanThrow 'TeamNotFound
                                                                :> Get '[JSON] TeamName))
                                                         :<|> (Named
                                                                 "update-team-status"
                                                                 ("status"
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow
                                                                            'InvalidTeamStatusUpdate
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                TeamStatusUpdate
                                                                              :> MultiVerb
                                                                                   'PUT
                                                                                   '[JSON]
                                                                                   '[RespondEmpty
                                                                                       200 "OK"]
                                                                                   ()))))
                                                               :<|> (("members"
                                                                      :> (Named
                                                                            "unchecked-add-team-member"
                                                                            (CanThrow
                                                                               'TooManyTeamMembers
                                                                             :> (CanThrow
                                                                                   'TooManyTeamMembersOnTeamWithLegalhold
                                                                                 :> (CanThrow
                                                                                       'TooManyTeamAdmins
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           NewTeamMember
                                                                                         :> MultiVerb
                                                                                              'POST
                                                                                              '[JSON]
                                                                                              '[RespondEmpty
                                                                                                  200
                                                                                                  "OK"]
                                                                                              ()))))
                                                                          :<|> (Named
                                                                                  "unchecked-get-team-members"
                                                                                  (QueryParam'
                                                                                     '[Strict]
                                                                                     "maxResults"
                                                                                     (Range
                                                                                        1
                                                                                        HardTruncationLimit
                                                                                        Int32)
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        TeamMemberList)
                                                                                :<|> (Named
                                                                                        "unchecked-get-team-member"
                                                                                        (Capture
                                                                                           "uid"
                                                                                           UserId
                                                                                         :> (CanThrow
                                                                                               'TeamMemberNotFound
                                                                                             :> Get
                                                                                                  '[JSON]
                                                                                                  TeamMember))
                                                                                      :<|> (Named
                                                                                              "can-user-join-team"
                                                                                              ("check"
                                                                                               :> (CanThrow
                                                                                                     'TooManyTeamMembersOnTeamWithLegalhold
                                                                                                   :> MultiVerb
                                                                                                        'GET
                                                                                                        '[JSON]
                                                                                                        '[RespondEmpty
                                                                                                            200
                                                                                                            "User can join"]
                                                                                                        ()))
                                                                                            :<|> Named
                                                                                                   "unchecked-update-team-member"
                                                                                                   (CanThrow
                                                                                                      'AccessDenied
                                                                                                    :> (CanThrow
                                                                                                          'InvalidPermissions
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> (CanThrow
                                                                                                                  'TeamMemberNotFound
                                                                                                                :> (CanThrow
                                                                                                                      'TooManyTeamAdmins
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              ('MissingPermission
                                                                                                                                 'Nothing)
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  NewTeamMember
                                                                                                                                :> MultiVerb
                                                                                                                                     'PUT
                                                                                                                                     '[JSON]
                                                                                                                                     '[RespondEmpty
                                                                                                                                         200
                                                                                                                                         ""]
                                                                                                                                     ())))))))))))))
                                                                     :<|> (Named
                                                                             "user-is-team-owner"
                                                                             ("is-team-owner"
                                                                              :> (Capture
                                                                                    "uid" UserId
                                                                                  :> (CanThrow
                                                                                        'AccessDenied
                                                                                      :> (CanThrow
                                                                                            'TeamMemberNotFound
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> MultiVerb
                                                                                                   'GET
                                                                                                   '[JSON]
                                                                                                   '[RespondEmpty
                                                                                                       200
                                                                                                       "User is team owner"]
                                                                                                   ())))))
                                                                           :<|> ("search-visibility"
                                                                                 :> (Named
                                                                                       "get-search-visibility-internal"
                                                                                       (Get
                                                                                          '[JSON]
                                                                                          TeamSearchVisibilityView)
                                                                                     :<|> Named
                                                                                            "set-search-visibility-internal"
                                                                                            (CanThrow
                                                                                               'TeamSearchVisibilityNotEnabled
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               TeamSearchVisibilityView
                                                                                                             :> MultiVerb
                                                                                                                  'PUT
                                                                                                                  '[JSON]
                                                                                                                  '[RespondEmpty
                                                                                                                      204
                                                                                                                      "OK"]
                                                                                                                  ()))))))))))))))))
                              :<|> ((Named
                                       "get-team-members"
                                       (CanThrow 'NonBindingTeam
                                        :> (CanThrow 'TeamNotFound
                                            :> ("users"
                                                :> (Capture "uid" UserId
                                                    :> ("team"
                                                        :> ("members"
                                                            :> Get '[JSON] TeamMemberList))))))
                                     :<|> (Named
                                             "get-team-id"
                                             (CanThrow 'NonBindingTeam
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("users"
                                                      :> (Capture "uid" UserId
                                                          :> ("team" :> Get '[JSON] TeamId)))))
                                           :<|> (Named
                                                   "test-get-clients"
                                                   ("test"
                                                    :> ("clients"
                                                        :> (ZUser :> Get '[JSON] [ClientId])))
                                                 :<|> (Named
                                                         "test-add-client"
                                                         ("clients"
                                                          :> (ZUser
                                                              :> (Capture "cid" ClientId
                                                                  :> MultiVerb
                                                                       'POST
                                                                       '[JSON]
                                                                       '[RespondEmpty 200 "OK"]
                                                                       ())))
                                                       :<|> (Named
                                                               "test-delete-client"
                                                               ("clients"
                                                                :> (ZUser
                                                                    :> (Capture "cid" ClientId
                                                                        :> MultiVerb
                                                                             'DELETE
                                                                             '[JSON]
                                                                             '[RespondEmpty
                                                                                 200 "OK"]
                                                                             ())))
                                                             :<|> (Named
                                                                     "add-service"
                                                                     ("services"
                                                                      :> (ReqBody '[JSON] Service
                                                                          :> MultiVerb
                                                                               'POST
                                                                               '[JSON]
                                                                               '[RespondEmpty
                                                                                   200 "OK"]
                                                                               ()))
                                                                   :<|> (Named
                                                                           "delete-service"
                                                                           ("services"
                                                                            :> (ReqBody
                                                                                  '[JSON] ServiceRef
                                                                                :> MultiVerb
                                                                                     'DELETE
                                                                                     '[JSON]
                                                                                     '[RespondEmpty
                                                                                         200 "OK"]
                                                                                     ()))
                                                                         :<|> (Named
                                                                                 "i-add-bot"
                                                                                 (CanThrow
                                                                                    ('ActionDenied
                                                                                       'AddConversationMember)
                                                                                  :> (CanThrow
                                                                                        'ConvNotFound
                                                                                      :> (CanThrow
                                                                                            'InvalidOperation
                                                                                          :> (CanThrow
                                                                                                'TooManyMembers
                                                                                              :> ("bots"
                                                                                                  :> (ZLocalUser
                                                                                                      :> (ZConn
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                AddBot
                                                                                                              :> Post
                                                                                                                   '[JSON]
                                                                                                                   Event))))))))
                                                                               :<|> (Named
                                                                                       "delete-bot"
                                                                                       (CanThrow
                                                                                          'ConvNotFound
                                                                                        :> (CanThrow
                                                                                              ('ActionDenied
                                                                                                 'RemoveConversationMember)
                                                                                            :> ("bots"
                                                                                                :> (ZLocalUser
                                                                                                    :> (ZOptConn
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              RemoveBot
                                                                                                            :> MultiVerb
                                                                                                                 'DELETE
                                                                                                                 '[JSON]
                                                                                                                 (UpdateResponses
                                                                                                                    "Bot not found"
                                                                                                                    "Bot deleted"
                                                                                                                    Event)
                                                                                                                 (UpdateResult
                                                                                                                    Event)))))))
                                                                                     :<|> (Named
                                                                                             "put-custom-backend"
                                                                                             ("custom-backend"
                                                                                              :> ("by-domain"
                                                                                                  :> (Capture
                                                                                                        "domain"
                                                                                                        Domain
                                                                                                      :> (ReqBody
                                                                                                            '[JSON]
                                                                                                            CustomBackend
                                                                                                          :> MultiVerb
                                                                                                               'PUT
                                                                                                               '[JSON]
                                                                                                               '[RespondEmpty
                                                                                                                   201
                                                                                                                   "OK"]
                                                                                                               ()))))
                                                                                           :<|> Named
                                                                                                  "delete-custom-backend"
                                                                                                  ("custom-backend"
                                                                                                   :> ("by-domain"
                                                                                                       :> (Capture
                                                                                                             "domain"
                                                                                                             Domain
                                                                                                           :> MultiVerb
                                                                                                                'DELETE
                                                                                                                '[JSON]
                                                                                                                '[RespondEmpty
                                                                                                                    200
                                                                                                                    "OK"]
                                                                                                                ())))))))))))))
                                    :<|> (Named
                                            "upsert-one2one"
                                            (Summary
                                               "Create or Update a connect or one2one conversation."
                                             :> ("conversations"
                                                 :> ("one2one"
                                                     :> ("upsert"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               UpsertOne2OneConversationRequest
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[RespondEmpty
                                                                      200 "Upsert One2One Policy"]
                                                                  ())))))
                                          :<|> ((((Named
                                                     '("iget", LegalholdConfig)
                                                     (Description ""
                                                      :> (Summary "Get config for legalhold"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("legalhold"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              LegalholdConfig))))))))))
                                                   :<|> (Named
                                                           '("iput", LegalholdConfig)
                                                           (Description ""
                                                            :> (Summary "Put config for legalhold"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany
                                                                                      '[ 'ActionDenied
                                                                                           'RemoveConversationMember,
                                                                                         'CannotEnableLegalHoldServiceLargeTeam,
                                                                                         'LegalHoldNotEnabled,
                                                                                         'LegalHoldDisableUnimplemented,
                                                                                         'LegalHoldServiceNotRegistered,
                                                                                         'UserLegalHoldIllegalOperation,
                                                                                         'LegalHoldCouldNotBlockConnections]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("legalhold"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             LegalholdConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                LegalholdConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch", LegalholdConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Patch config for legalhold"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[ 'ActionDenied
                                                                                                'RemoveConversationMember,
                                                                                              'CannotEnableLegalHoldServiceLargeTeam,
                                                                                              'LegalHoldNotEnabled,
                                                                                              'LegalHoldDisableUnimplemented,
                                                                                              'LegalHoldServiceNotRegistered,
                                                                                              'UserLegalHoldIllegalOperation,
                                                                                              'LegalHoldCouldNotBlockConnections]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("legalhold"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  LegalholdConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     LegalholdConfig)))))))))))))))
                                                  :<|> ((Named
                                                           '("iget", SSOConfig)
                                                           (Description ""
                                                            :> (Summary "Get config for sso"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("sso"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    SSOConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput", SSOConfig)
                                                                 (Description ""
                                                                  :> (Summary "Put config for sso"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("sso"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   SSOConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      SSOConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch", SSOConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for sso"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("sso"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        SSOConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           SSOConfig)))))))))))))))
                                                        :<|> ((Named
                                                                 '("iget",
                                                                   SearchVisibilityAvailableConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Get config for searchVisibility"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("searchVisibility"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          SearchVisibilityAvailableConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput",
                                                                         SearchVisibilityAvailableConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for searchVisibility"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("searchVisibility"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         SearchVisibilityAvailableConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            SearchVisibilityAvailableConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch",
                                                                              SearchVisibilityAvailableConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for searchVisibility"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("searchVisibility"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              SearchVisibilityAvailableConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 SearchVisibilityAvailableConfig)))))))))))))))
                                                              :<|> ((Named
                                                                       '("iget",
                                                                         SearchVisibilityInboundConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for searchVisibilityInbound"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("searchVisibilityInbound"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SearchVisibilityInboundConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               SearchVisibilityInboundConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for searchVisibilityInbound"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("searchVisibilityInbound"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               SearchVisibilityInboundConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  SearchVisibilityInboundConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    SearchVisibilityInboundConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for searchVisibilityInbound"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("searchVisibilityInbound"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    SearchVisibilityInboundConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       SearchVisibilityInboundConfig)))))))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               ValidateSAMLEmailsConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for validateSAMLemails"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("validateSAMLemails"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      ValidateSAMLEmailsConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     ValidateSAMLEmailsConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for validateSAMLemails"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("validateSAMLemails"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     ValidateSAMLEmailsConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        ValidateSAMLEmailsConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          ValidateSAMLEmailsConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for validateSAMLemails"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("validateSAMLemails"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          ValidateSAMLEmailsConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             ValidateSAMLEmailsConfig)))))))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     DigitalSignaturesConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for digitalSignatures"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("digitalSignatures"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            DigitalSignaturesConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           DigitalSignaturesConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for digitalSignatures"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("digitalSignatures"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           DigitalSignaturesConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              DigitalSignaturesConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                DigitalSignaturesConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for digitalSignatures"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("digitalSignatures"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                DigitalSignaturesConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   DigitalSignaturesConfig)))))))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           AppLockConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for appLock"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("appLock"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  AppLockConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 AppLockConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for appLock"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("appLock"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 AppLockConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    AppLockConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      AppLockConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for appLock"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("appLock"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      AppLockConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         AppLockConfig)))))))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 FileSharingConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for fileSharing"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("fileSharing"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        FileSharingConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       FileSharingConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for fileSharing"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("fileSharing"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       FileSharingConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          FileSharingConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            FileSharingConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for fileSharing"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("fileSharing"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            FileSharingConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               FileSharingConfig)))))))))))))))
                                                                                            :<|> (Named
                                                                                                    '("iget",
                                                                                                      ClassifiedDomainsConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Get config for classifiedDomains"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("classifiedDomains"
                                                                                                                                     :> Get
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             ClassifiedDomainsConfig))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             ConferenceCallingConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for conferenceCalling"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("conferenceCalling"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    ConferenceCallingConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   ConferenceCallingConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for conferenceCalling"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("conferenceCalling"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   ConferenceCallingConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      ConferenceCallingConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        ConferenceCallingConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for conferenceCalling"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("conferenceCalling"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        ConferenceCallingConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           ConferenceCallingConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   SelfDeletingMessagesConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for selfDeletingMessages"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("selfDeletingMessages"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          SelfDeletingMessagesConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         SelfDeletingMessagesConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for selfDeletingMessages"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("selfDeletingMessages"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         SelfDeletingMessagesConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            SelfDeletingMessagesConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              SelfDeletingMessagesConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for selfDeletingMessages"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("selfDeletingMessages"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              SelfDeletingMessagesConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 SelfDeletingMessagesConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         GuestLinksConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for conversationGuestLinks"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("conversationGuestLinks"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                GuestLinksConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               GuestLinksConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for conversationGuestLinks"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("conversationGuestLinks"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               GuestLinksConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  GuestLinksConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    GuestLinksConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for conversationGuestLinks"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    GuestLinksConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       GuestLinksConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               SndFactorPasswordChallengeConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for sndFactorPasswordChallenge"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("sndFactorPasswordChallenge"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      SndFactorPasswordChallengeConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     SndFactorPasswordChallengeConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for sndFactorPasswordChallenge"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("sndFactorPasswordChallenge"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     SndFactorPasswordChallengeConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        SndFactorPasswordChallengeConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          SndFactorPasswordChallengeConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for sndFactorPasswordChallenge"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          SndFactorPasswordChallengeConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                                                          :<|> ((Named
                                                                                                                                   '("iget",
                                                                                                                                     MLSConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for mls"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("mls"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MLSConfig))))))))))
                                                                                                                                 :<|> (Named
                                                                                                                                         '("iput",
                                                                                                                                           MLSConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Put config for mls"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("mls"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Feature
                                                                                                                                                                                           MLSConfig)
                                                                                                                                                                                      :> Put
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              MLSConfig)))))))))))))
                                                                                                                                       :<|> Named
                                                                                                                                              '("ipatch",
                                                                                                                                                MLSConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Patch config for mls"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("mls"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                MLSConfig)
                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   MLSConfig)))))))))))))))
                                                                                                                                :<|> ((Named
                                                                                                                                         '("iget",
                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                                                       :<|> (Named
                                                                                                                                               '("iput",
                                                                                                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                          '[]
                                                                                                                                                                        :> ("teams"
                                                                                                                                                                            :> (Capture
                                                                                                                                                                                  "tid"
                                                                                                                                                                                  TeamId
                                                                                                                                                                                :> ("features"
                                                                                                                                                                                    :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (Feature
                                                                                                                                                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                            :> Put
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                                                             :<|> Named
                                                                                                                                                    '("ipatch",
                                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                    (Description
                                                                                                                                                       ""
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                                 :> Patch
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                                                      :<|> ((Named
                                                                                                                                               '("iget",
                                                                                                                                                 OutlookCalIntegrationConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Get config for outlookCalIntegration"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("outlookCalIntegration"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        OutlookCalIntegrationConfig))))))))))
                                                                                                                                             :<|> (Named
                                                                                                                                                     '("iput",
                                                                                                                                                       OutlookCalIntegrationConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Put config for outlookCalIntegration"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                          :> (CanThrowMany
                                                                                                                                                                                '[]
                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                        "tid"
                                                                                                                                                                                        TeamId
                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                          :> ("outlookCalIntegration"
                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (Feature
                                                                                                                                                                                                       OutlookCalIntegrationConfig)
                                                                                                                                                                                                  :> Put
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          OutlookCalIntegrationConfig)))))))))))))
                                                                                                                                                   :<|> Named
                                                                                                                                                          '("ipatch",
                                                                                                                                                            OutlookCalIntegrationConfig)
                                                                                                                                                          (Description
                                                                                                                                                             ""
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Patch config for outlookCalIntegration"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('MissingPermission
                                                                                                                                                                        'Nothing)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 TeamFeatureError
                                                                                                                                                                               :> (CanThrowMany
                                                                                                                                                                                     '[]
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> ("outlookCalIntegration"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                                                                            OutlookCalIntegrationConfig)
                                                                                                                                                                                                       :> Patch
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               OutlookCalIntegrationConfig)))))))))))))))
                                                                                                                                            :<|> ((Named
                                                                                                                                                     '("iget",
                                                                                                                                                       MlsE2EIdConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Get config for mlsE2EId"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("mlsE2EId"
                                                                                                                                                                                      :> Get
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              MlsE2EIdConfig))))))))))
                                                                                                                                                   :<|> (Named
                                                                                                                                                           '("iput",
                                                                                                                                                             MlsE2EIdConfig)
                                                                                                                                                           (Description
                                                                                                                                                              ""
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Put config for mlsE2EId"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  TeamFeatureError
                                                                                                                                                                                :> (CanThrowMany
                                                                                                                                                                                      '[]
                                                                                                                                                                                    :> ("teams"
                                                                                                                                                                                        :> (Capture
                                                                                                                                                                                              "tid"
                                                                                                                                                                                              TeamId
                                                                                                                                                                                            :> ("features"
                                                                                                                                                                                                :> ("mlsE2EId"
                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (Feature
                                                                                                                                                                                                             MlsE2EIdConfig)
                                                                                                                                                                                                        :> Put
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                MlsE2EIdConfig)))))))))))))
                                                                                                                                                         :<|> Named
                                                                                                                                                                '("ipatch",
                                                                                                                                                                  MlsE2EIdConfig)
                                                                                                                                                                (Description
                                                                                                                                                                   ""
                                                                                                                                                                 :> (Summary
                                                                                                                                                                       "Patch config for mlsE2EId"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('MissingPermission
                                                                                                                                                                              'Nothing)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       TeamFeatureError
                                                                                                                                                                                     :> (CanThrowMany
                                                                                                                                                                                           '[]
                                                                                                                                                                                         :> ("teams"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "tid"
                                                                                                                                                                                                   TeamId
                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                     :> ("mlsE2EId"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                                                                  MlsE2EIdConfig)
                                                                                                                                                                                                             :> Patch
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     MlsE2EIdConfig)))))))))))))))
                                                                                                                                                  :<|> ((Named
                                                                                                                                                           '("iget",
                                                                                                                                                             MlsMigrationConfig)
                                                                                                                                                           (Description
                                                                                                                                                              ""
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Get config for mlsMigration"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                :> (Capture
                                                                                                                                                                                      "tid"
                                                                                                                                                                                      TeamId
                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                        :> ("mlsMigration"
                                                                                                                                                                                            :> Get
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    MlsMigrationConfig))))))))))
                                                                                                                                                         :<|> (Named
                                                                                                                                                                 '("iput",
                                                                                                                                                                   MlsMigrationConfig)
                                                                                                                                                                 (Description
                                                                                                                                                                    ""
                                                                                                                                                                  :> (Summary
                                                                                                                                                                        "Put config for mlsMigration"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            ('MissingPermission
                                                                                                                                                                               'Nothing)
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        TeamFeatureError
                                                                                                                                                                                      :> (CanThrowMany
                                                                                                                                                                                            '[]
                                                                                                                                                                                          :> ("teams"
                                                                                                                                                                                              :> (Capture
                                                                                                                                                                                                    "tid"
                                                                                                                                                                                                    TeamId
                                                                                                                                                                                                  :> ("features"
                                                                                                                                                                                                      :> ("mlsMigration"
                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (Feature
                                                                                                                                                                                                                   MlsMigrationConfig)
                                                                                                                                                                                                              :> Put
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                                      MlsMigrationConfig)))))))))))))
                                                                                                                                                               :<|> Named
                                                                                                                                                                      '("ipatch",
                                                                                                                                                                        MlsMigrationConfig)
                                                                                                                                                                      (Description
                                                                                                                                                                         ""
                                                                                                                                                                       :> (Summary
                                                                                                                                                                             "Patch config for mlsMigration"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('MissingPermission
                                                                                                                                                                                    'Nothing)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             TeamFeatureError
                                                                                                                                                                                           :> (CanThrowMany
                                                                                                                                                                                                 '[]
                                                                                                                                                                                               :> ("teams"
                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                         "tid"
                                                                                                                                                                                                         TeamId
                                                                                                                                                                                                       :> ("features"
                                                                                                                                                                                                           :> ("mlsMigration"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                                                                        MlsMigrationConfig)
                                                                                                                                                                                                                   :> Patch
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                           MlsMigrationConfig)))))))))))))))
                                                                                                                                                        :<|> ((Named
                                                                                                                                                                 '("iget",
                                                                                                                                                                   EnforceFileDownloadLocationConfig)
                                                                                                                                                                 (Description
                                                                                                                                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                  :> (Summary
                                                                                                                                                                        "Get config for enforceFileDownloadLocation"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            ('MissingPermission
                                                                                                                                                                               'Nothing)
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> ("teams"
                                                                                                                                                                                      :> (Capture
                                                                                                                                                                                            "tid"
                                                                                                                                                                                            TeamId
                                                                                                                                                                                          :> ("features"
                                                                                                                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                  :> Get
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                                               :<|> (Named
                                                                                                                                                                       '("iput",
                                                                                                                                                                         EnforceFileDownloadLocationConfig)
                                                                                                                                                                       (Description
                                                                                                                                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                        :> (Summary
                                                                                                                                                                              "Put config for enforceFileDownloadLocation"
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  ('MissingPermission
                                                                                                                                                                                     'Nothing)
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              TeamFeatureError
                                                                                                                                                                                            :> (CanThrowMany
                                                                                                                                                                                                  '[]
                                                                                                                                                                                                :> ("teams"
                                                                                                                                                                                                    :> (Capture
                                                                                                                                                                                                          "tid"
                                                                                                                                                                                                          TeamId
                                                                                                                                                                                                        :> ("features"
                                                                                                                                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (Feature
                                                                                                                                                                                                                         EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                                    :> Put
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                                                            EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                                                     :<|> Named
                                                                                                                                                                            '("ipatch",
                                                                                                                                                                              EnforceFileDownloadLocationConfig)
                                                                                                                                                                            (Description
                                                                                                                                                                               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                             :> (Summary
                                                                                                                                                                                   "Patch config for enforceFileDownloadLocation"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('MissingPermission
                                                                                                                                                                                          'Nothing)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   TeamFeatureError
                                                                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                                                                       '[]
                                                                                                                                                                                                     :> ("teams"
                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                               "tid"
                                                                                                                                                                                                               TeamId
                                                                                                                                                                                                             :> ("features"
                                                                                                                                                                                                                 :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                                                                              EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                                         :> Patch
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                 EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                                              :<|> (Named
                                                                                                                                                                      '("iget",
                                                                                                                                                                        LimitedEventFanoutConfig)
                                                                                                                                                                      (Description
                                                                                                                                                                         ""
                                                                                                                                                                       :> (Summary
                                                                                                                                                                             "Get config for limitedEventFanout"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('MissingPermission
                                                                                                                                                                                    'Nothing)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("teams"
                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                 "tid"
                                                                                                                                                                                                 TeamId
                                                                                                                                                                                               :> ("features"
                                                                                                                                                                                                   :> ("limitedEventFanout"
                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               LimitedEventFanoutConfig))))))))))
                                                                                                                                                                    :<|> (Named
                                                                                                                                                                            '("iput",
                                                                                                                                                                              LimitedEventFanoutConfig)
                                                                                                                                                                            (Description
                                                                                                                                                                               ""
                                                                                                                                                                             :> (Summary
                                                                                                                                                                                   "Put config for limitedEventFanout"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('MissingPermission
                                                                                                                                                                                          'Nothing)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   TeamFeatureError
                                                                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                                                                       '[]
                                                                                                                                                                                                     :> ("teams"
                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                               "tid"
                                                                                                                                                                                                               TeamId
                                                                                                                                                                                                             :> ("features"
                                                                                                                                                                                                                 :> ("limitedEventFanout"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           (Feature
                                                                                                                                                                                                                              LimitedEventFanoutConfig)
                                                                                                                                                                                                                         :> Put
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                 LimitedEventFanoutConfig)))))))))))))
                                                                                                                                                                          :<|> Named
                                                                                                                                                                                 '("ipatch",
                                                                                                                                                                                   LimitedEventFanoutConfig)
                                                                                                                                                                                 (Description
                                                                                                                                                                                    ""
                                                                                                                                                                                  :> (Summary
                                                                                                                                                                                        "Patch config for limitedEventFanout"
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            ('MissingPermission
                                                                                                                                                                                               'Nothing)
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                        TeamFeatureError
                                                                                                                                                                                                      :> (CanThrowMany
                                                                                                                                                                                                            '[]
                                                                                                                                                                                                          :> ("teams"
                                                                                                                                                                                                              :> (Capture
                                                                                                                                                                                                                    "tid"
                                                                                                                                                                                                                    TeamId
                                                                                                                                                                                                                  :> ("features"
                                                                                                                                                                                                                      :> ("limitedEventFanout"
                                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                (LockableFeaturePatch
                                                                                                                                                                                                                                   LimitedEventFanoutConfig)
                                                                                                                                                                                                                              :> Patch
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                                                      LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                                                 :<|> (Named
                                                         '("ilock", FileSharingConfig)
                                                         (Summary "(Un-)lock fileSharing"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("fileSharing"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock", ConferenceCallingConfig)
                                                               (Summary
                                                                  "(Un-)lock conferenceCalling"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("conferenceCalling"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock",
                                                                       SelfDeletingMessagesConfig)
                                                                     (Summary
                                                                        "(Un-)lock selfDeletingMessages"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("selfDeletingMessages"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock",
                                                                             GuestLinksConfig)
                                                                           (Summary
                                                                              "(Un-)lock conversationGuestLinks"
                                                                            :> (Description ""
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("conversationGuestLinks"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("ilock",
                                                                                   SndFactorPasswordChallengeConfig)
                                                                                 (Summary
                                                                                    "(Un-)lock sndFactorPasswordChallenge"
                                                                                  :> (Description ""
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("sndFactorPasswordChallenge"
                                                                                                              :> (Capture
                                                                                                                    "lockStatus"
                                                                                                                    LockStatus
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       LockStatusResponse)))))))))
                                                                               :<|> (Named
                                                                                       '("ilock",
                                                                                         MLSConfig)
                                                                                       (Summary
                                                                                          "(Un-)lock mls"
                                                                                        :> (Description
                                                                                              ""
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mls"
                                                                                                                    :> (Capture
                                                                                                                          "lockStatus"
                                                                                                                          LockStatus
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             LockStatusResponse)))))))))
                                                                                     :<|> (Named
                                                                                             '("ilock",
                                                                                               OutlookCalIntegrationConfig)
                                                                                             (Summary
                                                                                                "(Un-)lock outlookCalIntegration"
                                                                                              :> (Description
                                                                                                    ""
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("outlookCalIntegration"
                                                                                                                          :> (Capture
                                                                                                                                "lockStatus"
                                                                                                                                LockStatus
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   LockStatusResponse)))))))))
                                                                                           :<|> (Named
                                                                                                   '("ilock",
                                                                                                     MlsE2EIdConfig)
                                                                                                   (Summary
                                                                                                      "(Un-)lock mlsE2EId"
                                                                                                    :> (Description
                                                                                                          ""
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mlsE2EId"
                                                                                                                                :> (Capture
                                                                                                                                      "lockStatus"
                                                                                                                                      LockStatus
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         LockStatusResponse)))))))))
                                                                                                 :<|> (Named
                                                                                                         '("ilock",
                                                                                                           MlsMigrationConfig)
                                                                                                         (Summary
                                                                                                            "(Un-)lock mlsMigration"
                                                                                                          :> (Description
                                                                                                                ""
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("mlsMigration"
                                                                                                                                      :> (Capture
                                                                                                                                            "lockStatus"
                                                                                                                                            LockStatus
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               LockStatusResponse)))))))))
                                                                                                       :<|> (Named
                                                                                                               '("ilock",
                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                               (Summary
                                                                                                                  "(Un-)lock enforceFileDownloadLocation"
                                                                                                                :> (Description
                                                                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("enforceFileDownloadLocation"
                                                                                                                                            :> (Capture
                                                                                                                                                  "lockStatus"
                                                                                                                                                  LockStatus
                                                                                                                                                :> Put
                                                                                                                                                     '[JSON]
                                                                                                                                                     LockStatusResponse)))))))))
                                                                                                             :<|> (Named
                                                                                                                     '("igetmulti",
                                                                                                                       SearchVisibilityInboundConfig)
                                                                                                                     (Summary
                                                                                                                        "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                                                      :> ("features-multi-teams"
                                                                                                                          :> ("searchVisibilityInbound"
                                                                                                                              :> (ReqBody
                                                                                                                                    '[JSON]
                                                                                                                                    TeamFeatureNoConfigMultiRequest
                                                                                                                                  :> Post
                                                                                                                                       '[JSON]
                                                                                                                                       (TeamFeatureNoConfigMultiResponse
                                                                                                                                          SearchVisibilityInboundConfig)))))
                                                                                                                   :<|> Named
                                                                                                                          "feature-configs-internal"
                                                                                                                          (Summary
                                                                                                                             "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> (CanThrow
                                                                                                                                     ('MissingPermission
                                                                                                                                        'Nothing)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotATeamMember
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TeamNotFound
                                                                                                                                           :> (QueryParam'
                                                                                                                                                 '[Optional,
                                                                                                                                                   Strict,
                                                                                                                                                   Description
                                                                                                                                                     "Optional user id"]
                                                                                                                                                 "user_id"
                                                                                                                                                 UserId
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    AllTeamFeatures))))))))))))))))))
                                                :<|> (IFederationAPI
                                                      :<|> (IConversationAPI :<|> IEJPDAPI))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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-clients" ServerT
  (Summary "Get mls conversation client list"
   :> (CanThrow 'ConvNotFound
       :> ("group"
           :> (Capture "gid" GroupId
               :> MultiVerb
                    'GET '[JSON] '[Respond 200 "Clients" ClientList] ClientList))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Get mls conversation client list"
            :> (CanThrow 'ConvNotFound
                :> ("group"
                    :> (Capture "gid" GroupId
                        :> MultiVerb
                             'GET '[JSON] '[Respond 200 "Clients" ClientList] ClientList)))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
GroupId
-> 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]
     ClientList
forall (r :: EffectRow).
Members '[MemberStore, Error (Tagged 'ConvNotFound ())] r =>
GroupId -> Sem r ClientList
iGetMLSClientListForConv
      API
  (Named
     "get-conversation-clients"
     (Summary "Get mls conversation client list"
      :> (CanThrow 'ConvNotFound
          :> ("group"
              :> (Capture "gid" GroupId
                  :> MultiVerb
                       'GET '[JSON] '[Respond 200 "Clients" ClientList] ClientList)))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "guard-legalhold-policy-conflicts"
        ("guard-legalhold-policy-conflicts"
         :> (CanThrow 'MissingLegalholdConsent
             :> (CanThrow 'MissingLegalholdConsentOldClients
                 :> (ReqBody '[JSON] GuardLegalholdPolicyConflicts
                     :> MultiVerb
                          'PUT '[JSON] '[RespondEmpty 200 "Guard Legalhold Policy"] ()))))
      :<|> (("legalhold"
             :> ("whitelisted-teams"
                 :> (Capture "tid" TeamId
                     :> (Named
                           "set-team-legalhold-whitelisted"
                           (MultiVerb
                              'PUT '[JSON] '[RespondEmpty 200 "Team Legalhold Whitelisted"] ())
                         :<|> (Named
                                 "unset-team-legalhold-whitelisted"
                                 (MultiVerb
                                    'DELETE
                                    '[JSON]
                                    '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
                                    ())
                               :<|> Named
                                      "get-team-legalhold-whitelisted"
                                      (MultiVerb
                                         'GET
                                         '[JSON]
                                         '[RespondEmpty 404 "Team not Legalhold Whitelisted",
                                           RespondEmpty 200 "Team Legalhold Whitelisted"]
                                         Bool))))))
            :<|> (("teams"
                   :> (Capture "tid" TeamId
                       :> (Named
                             "get-team-internal"
                             (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
                           :<|> (Named
                                   "create-binding-team"
                                   (ZUser
                                    :> (ReqBody '[JSON] BindingNewTeam
                                        :> MultiVerb
                                             'PUT
                                             '[JSON]
                                             '[WithHeaders
                                                 '[Header "Location" TeamId]
                                                 TeamId
                                                 (RespondEmpty 201 "OK")]
                                             TeamId))
                                 :<|> (Named
                                         "delete-binding-team"
                                         (CanThrow 'NoBindingTeam
                                          :> (CanThrow 'NotAOneMemberTeam
                                              :> (CanThrow 'DeleteQueueFull
                                                  :> (CanThrow 'TeamNotFound
                                                      :> (QueryFlag "force"
                                                          :> MultiVerb
                                                               'DELETE
                                                               '[JSON]
                                                               '[RespondEmpty 202 "OK"]
                                                               ())))))
                                       :<|> (Named
                                               "get-team-name"
                                               ("name"
                                                :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
                                             :<|> (Named
                                                     "update-team-status"
                                                     ("status"
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow 'InvalidTeamStatusUpdate
                                                              :> (ReqBody '[JSON] TeamStatusUpdate
                                                                  :> MultiVerb
                                                                       'PUT
                                                                       '[JSON]
                                                                       '[RespondEmpty 200 "OK"]
                                                                       ()))))
                                                   :<|> (("members"
                                                          :> (Named
                                                                "unchecked-add-team-member"
                                                                (CanThrow 'TooManyTeamMembers
                                                                 :> (CanThrow
                                                                       'TooManyTeamMembersOnTeamWithLegalhold
                                                                     :> (CanThrow 'TooManyTeamAdmins
                                                                         :> (ReqBody
                                                                               '[JSON] NewTeamMember
                                                                             :> MultiVerb
                                                                                  'POST
                                                                                  '[JSON]
                                                                                  '[RespondEmpty
                                                                                      200 "OK"]
                                                                                  ()))))
                                                              :<|> (Named
                                                                      "unchecked-get-team-members"
                                                                      (QueryParam'
                                                                         '[Strict]
                                                                         "maxResults"
                                                                         (Range
                                                                            1
                                                                            HardTruncationLimit
                                                                            Int32)
                                                                       :> Get
                                                                            '[JSON] TeamMemberList)
                                                                    :<|> (Named
                                                                            "unchecked-get-team-member"
                                                                            (Capture "uid" UserId
                                                                             :> (CanThrow
                                                                                   'TeamMemberNotFound
                                                                                 :> Get
                                                                                      '[JSON]
                                                                                      TeamMember))
                                                                          :<|> (Named
                                                                                  "can-user-join-team"
                                                                                  ("check"
                                                                                   :> (CanThrow
                                                                                         'TooManyTeamMembersOnTeamWithLegalhold
                                                                                       :> MultiVerb
                                                                                            'GET
                                                                                            '[JSON]
                                                                                            '[RespondEmpty
                                                                                                200
                                                                                                "User can join"]
                                                                                            ()))
                                                                                :<|> Named
                                                                                       "unchecked-update-team-member"
                                                                                       (CanThrow
                                                                                          'AccessDenied
                                                                                        :> (CanThrow
                                                                                              'InvalidPermissions
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> (CanThrow
                                                                                                      'TeamMemberNotFound
                                                                                                    :> (CanThrow
                                                                                                          'TooManyTeamAdmins
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  ('MissingPermission
                                                                                                                     'Nothing)
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      NewTeamMember
                                                                                                                    :> MultiVerb
                                                                                                                         'PUT
                                                                                                                         '[JSON]
                                                                                                                         '[RespondEmpty
                                                                                                                             200
                                                                                                                             ""]
                                                                                                                         ())))))))))))))
                                                         :<|> (Named
                                                                 "user-is-team-owner"
                                                                 ("is-team-owner"
                                                                  :> (Capture "uid" UserId
                                                                      :> (CanThrow 'AccessDenied
                                                                          :> (CanThrow
                                                                                'TeamMemberNotFound
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> MultiVerb
                                                                                       'GET
                                                                                       '[JSON]
                                                                                       '[RespondEmpty
                                                                                           200
                                                                                           "User is team owner"]
                                                                                       ())))))
                                                               :<|> ("search-visibility"
                                                                     :> (Named
                                                                           "get-search-visibility-internal"
                                                                           (Get
                                                                              '[JSON]
                                                                              TeamSearchVisibilityView)
                                                                         :<|> Named
                                                                                "set-search-visibility-internal"
                                                                                (CanThrow
                                                                                   'TeamSearchVisibilityNotEnabled
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   TeamSearchVisibilityView
                                                                                                 :> MultiVerb
                                                                                                      'PUT
                                                                                                      '[JSON]
                                                                                                      '[RespondEmpty
                                                                                                          204
                                                                                                          "OK"]
                                                                                                      ()))))))))))))))))
                  :<|> ((Named
                           "get-team-members"
                           (CanThrow 'NonBindingTeam
                            :> (CanThrow 'TeamNotFound
                                :> ("users"
                                    :> (Capture "uid" UserId
                                        :> ("team" :> ("members" :> Get '[JSON] TeamMemberList))))))
                         :<|> (Named
                                 "get-team-id"
                                 (CanThrow 'NonBindingTeam
                                  :> (CanThrow 'TeamNotFound
                                      :> ("users"
                                          :> (Capture "uid" UserId
                                              :> ("team" :> Get '[JSON] TeamId)))))
                               :<|> (Named
                                       "test-get-clients"
                                       ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
                                     :<|> (Named
                                             "test-add-client"
                                             ("clients"
                                              :> (ZUser
                                                  :> (Capture "cid" ClientId
                                                      :> MultiVerb
                                                           'POST
                                                           '[JSON]
                                                           '[RespondEmpty 200 "OK"]
                                                           ())))
                                           :<|> (Named
                                                   "test-delete-client"
                                                   ("clients"
                                                    :> (ZUser
                                                        :> (Capture "cid" ClientId
                                                            :> MultiVerb
                                                                 'DELETE
                                                                 '[JSON]
                                                                 '[RespondEmpty 200 "OK"]
                                                                 ())))
                                                 :<|> (Named
                                                         "add-service"
                                                         ("services"
                                                          :> (ReqBody '[JSON] Service
                                                              :> MultiVerb
                                                                   'POST
                                                                   '[JSON]
                                                                   '[RespondEmpty 200 "OK"]
                                                                   ()))
                                                       :<|> (Named
                                                               "delete-service"
                                                               ("services"
                                                                :> (ReqBody '[JSON] ServiceRef
                                                                    :> MultiVerb
                                                                         'DELETE
                                                                         '[JSON]
                                                                         '[RespondEmpty 200 "OK"]
                                                                         ()))
                                                             :<|> (Named
                                                                     "i-add-bot"
                                                                     (CanThrow
                                                                        ('ActionDenied
                                                                           'AddConversationMember)
                                                                      :> (CanThrow 'ConvNotFound
                                                                          :> (CanThrow
                                                                                'InvalidOperation
                                                                              :> (CanThrow
                                                                                    'TooManyMembers
                                                                                  :> ("bots"
                                                                                      :> (ZLocalUser
                                                                                          :> (ZConn
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    AddBot
                                                                                                  :> Post
                                                                                                       '[JSON]
                                                                                                       Event))))))))
                                                                   :<|> (Named
                                                                           "delete-bot"
                                                                           (CanThrow 'ConvNotFound
                                                                            :> (CanThrow
                                                                                  ('ActionDenied
                                                                                     'RemoveConversationMember)
                                                                                :> ("bots"
                                                                                    :> (ZLocalUser
                                                                                        :> (ZOptConn
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  RemoveBot
                                                                                                :> MultiVerb
                                                                                                     'DELETE
                                                                                                     '[JSON]
                                                                                                     (UpdateResponses
                                                                                                        "Bot not found"
                                                                                                        "Bot deleted"
                                                                                                        Event)
                                                                                                     (UpdateResult
                                                                                                        Event)))))))
                                                                         :<|> (Named
                                                                                 "put-custom-backend"
                                                                                 ("custom-backend"
                                                                                  :> ("by-domain"
                                                                                      :> (Capture
                                                                                            "domain"
                                                                                            Domain
                                                                                          :> (ReqBody
                                                                                                '[JSON]
                                                                                                CustomBackend
                                                                                              :> MultiVerb
                                                                                                   'PUT
                                                                                                   '[JSON]
                                                                                                   '[RespondEmpty
                                                                                                       201
                                                                                                       "OK"]
                                                                                                   ()))))
                                                                               :<|> Named
                                                                                      "delete-custom-backend"
                                                                                      ("custom-backend"
                                                                                       :> ("by-domain"
                                                                                           :> (Capture
                                                                                                 "domain"
                                                                                                 Domain
                                                                                               :> MultiVerb
                                                                                                    'DELETE
                                                                                                    '[JSON]
                                                                                                    '[RespondEmpty
                                                                                                        200
                                                                                                        "OK"]
                                                                                                    ())))))))))))))
                        :<|> (Named
                                "upsert-one2one"
                                (Summary "Create or Update a connect or one2one conversation."
                                 :> ("conversations"
                                     :> ("one2one"
                                         :> ("upsert"
                                             :> (ReqBody '[JSON] UpsertOne2OneConversationRequest
                                                 :> MultiVerb
                                                      'POST
                                                      '[JSON]
                                                      '[RespondEmpty 200 "Upsert One2One Policy"]
                                                      ())))))
                              :<|> ((((Named
                                         '("iget", LegalholdConfig)
                                         (Description ""
                                          :> (Summary "Get config for legalhold"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("legalhold"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  LegalholdConfig))))))))))
                                       :<|> (Named
                                               '("iput", LegalholdConfig)
                                               (Description ""
                                                :> (Summary "Put config for legalhold"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> (CanThrowMany
                                                                          '[ 'ActionDenied
                                                                               'RemoveConversationMember,
                                                                             'CannotEnableLegalHoldServiceLargeTeam,
                                                                             'LegalHoldNotEnabled,
                                                                             'LegalHoldDisableUnimplemented,
                                                                             'LegalHoldServiceNotRegistered,
                                                                             'UserLegalHoldIllegalOperation,
                                                                             'LegalHoldCouldNotBlockConnections]
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("legalhold"
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              (Feature
                                                                                                 LegalholdConfig)
                                                                                            :> Put
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    LegalholdConfig)))))))))))))
                                             :<|> Named
                                                    '("ipatch", LegalholdConfig)
                                                    (Description ""
                                                     :> (Summary "Patch config for legalhold"
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany
                                                                               '[ 'ActionDenied
                                                                                    'RemoveConversationMember,
                                                                                  'CannotEnableLegalHoldServiceLargeTeam,
                                                                                  'LegalHoldNotEnabled,
                                                                                  'LegalHoldDisableUnimplemented,
                                                                                  'LegalHoldServiceNotRegistered,
                                                                                  'UserLegalHoldIllegalOperation,
                                                                                  'LegalHoldCouldNotBlockConnections]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("legalhold"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (LockableFeaturePatch
                                                                                                      LegalholdConfig)
                                                                                                 :> Patch
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         LegalholdConfig)))))))))))))))
                                      :<|> ((Named
                                               '("iget", SSOConfig)
                                               (Description ""
                                                :> (Summary "Get config for sso"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("sso"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SSOConfig))))))))))
                                             :<|> (Named
                                                     '("iput", SSOConfig)
                                                     (Description ""
                                                      :> (Summary "Put config for sso"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany '[]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("sso"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (Feature
                                                                                                       SSOConfig)
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          SSOConfig)))))))))))))
                                                   :<|> Named
                                                          '("ipatch", SSOConfig)
                                                          (Description ""
                                                           :> (Summary "Patch config for sso"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("sso"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (LockableFeaturePatch
                                                                                                            SSOConfig)
                                                                                                       :> Patch
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               SSOConfig)))))))))))))))
                                            :<|> ((Named
                                                     '("iget", SearchVisibilityAvailableConfig)
                                                     (Description ""
                                                      :> (Summary "Get config for searchVisibility"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("searchVisibility"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              SearchVisibilityAvailableConfig))))))))))
                                                   :<|> (Named
                                                           '("iput",
                                                             SearchVisibilityAvailableConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Put config for searchVisibility"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("searchVisibility"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             SearchVisibilityAvailableConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SearchVisibilityAvailableConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch",
                                                                  SearchVisibilityAvailableConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Patch config for searchVisibility"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("searchVisibility"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  SearchVisibilityAvailableConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     SearchVisibilityAvailableConfig)))))))))))))))
                                                  :<|> ((Named
                                                           '("iget", SearchVisibilityInboundConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Get config for searchVisibilityInbound"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("searchVisibilityInbound"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    SearchVisibilityInboundConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput",
                                                                   SearchVisibilityInboundConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Put config for searchVisibilityInbound"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("searchVisibilityInbound"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   SearchVisibilityInboundConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      SearchVisibilityInboundConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch",
                                                                        SearchVisibilityInboundConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for searchVisibilityInbound"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("searchVisibilityInbound"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        SearchVisibilityInboundConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           SearchVisibilityInboundConfig)))))))))))))))
                                                        :<|> ((Named
                                                                 '("iget", ValidateSAMLEmailsConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Get config for validateSAMLemails"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("validateSAMLemails"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          ValidateSAMLEmailsConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput",
                                                                         ValidateSAMLEmailsConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for validateSAMLemails"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("validateSAMLemails"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         ValidateSAMLEmailsConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            ValidateSAMLEmailsConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch",
                                                                              ValidateSAMLEmailsConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for validateSAMLemails"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("validateSAMLemails"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              ValidateSAMLEmailsConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 ValidateSAMLEmailsConfig)))))))))))))))
                                                              :<|> ((Named
                                                                       '("iget",
                                                                         DigitalSignaturesConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for digitalSignatures"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("digitalSignatures"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                DigitalSignaturesConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               DigitalSignaturesConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for digitalSignatures"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("digitalSignatures"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               DigitalSignaturesConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  DigitalSignaturesConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    DigitalSignaturesConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for digitalSignatures"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("digitalSignatures"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    DigitalSignaturesConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       DigitalSignaturesConfig)))))))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               AppLockConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for appLock"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("appLock"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      AppLockConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     AppLockConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for appLock"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("appLock"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     AppLockConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        AppLockConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          AppLockConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for appLock"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("appLock"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          AppLockConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             AppLockConfig)))))))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     FileSharingConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for fileSharing"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("fileSharing"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            FileSharingConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           FileSharingConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for fileSharing"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("fileSharing"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           FileSharingConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              FileSharingConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                FileSharingConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for fileSharing"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("fileSharing"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                FileSharingConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   FileSharingConfig)))))))))))))))
                                                                                :<|> (Named
                                                                                        '("iget",
                                                                                          ClassifiedDomainsConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Get config for classifiedDomains"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("classifiedDomains"
                                                                                                                         :> Get
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 ClassifiedDomainsConfig))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 ConferenceCallingConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for conferenceCalling"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("conferenceCalling"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        ConferenceCallingConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       ConferenceCallingConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for conferenceCalling"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("conferenceCalling"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       ConferenceCallingConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          ConferenceCallingConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            ConferenceCallingConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for conferenceCalling"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("conferenceCalling"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            ConferenceCallingConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               ConferenceCallingConfig)))))))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       SelfDeletingMessagesConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for selfDeletingMessages"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("selfDeletingMessages"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              SelfDeletingMessagesConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             SelfDeletingMessagesConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for selfDeletingMessages"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("selfDeletingMessages"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             SelfDeletingMessagesConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                SelfDeletingMessagesConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  SelfDeletingMessagesConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for selfDeletingMessages"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("selfDeletingMessages"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  SelfDeletingMessagesConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     SelfDeletingMessagesConfig)))))))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             GuestLinksConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for conversationGuestLinks"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("conversationGuestLinks"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    GuestLinksConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   GuestLinksConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for conversationGuestLinks"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("conversationGuestLinks"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   GuestLinksConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      GuestLinksConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        GuestLinksConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for conversationGuestLinks"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        GuestLinksConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           GuestLinksConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   SndFactorPasswordChallengeConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for sndFactorPasswordChallenge"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("sndFactorPasswordChallenge"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          SndFactorPasswordChallengeConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         SndFactorPasswordChallengeConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for sndFactorPasswordChallenge"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("sndFactorPasswordChallenge"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         SndFactorPasswordChallengeConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            SndFactorPasswordChallengeConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              SndFactorPasswordChallengeConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for sndFactorPasswordChallenge"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("sndFactorPasswordChallenge"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              SndFactorPasswordChallengeConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         MLSConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for mls"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("mls"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                MLSConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               MLSConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for mls"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("mls"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               MLSConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  MLSConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    MLSConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for mls"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("mls"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    MLSConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       MLSConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                                          :<|> ((Named
                                                                                                                                   '("iget",
                                                                                                                                     OutlookCalIntegrationConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for outlookCalIntegration"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("outlookCalIntegration"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            OutlookCalIntegrationConfig))))))))))
                                                                                                                                 :<|> (Named
                                                                                                                                         '("iput",
                                                                                                                                           OutlookCalIntegrationConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Put config for outlookCalIntegration"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("outlookCalIntegration"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Feature
                                                                                                                                                                                           OutlookCalIntegrationConfig)
                                                                                                                                                                                      :> Put
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              OutlookCalIntegrationConfig)))))))))))))
                                                                                                                                       :<|> Named
                                                                                                                                              '("ipatch",
                                                                                                                                                OutlookCalIntegrationConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Patch config for outlookCalIntegration"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("outlookCalIntegration"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                OutlookCalIntegrationConfig)
                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   OutlookCalIntegrationConfig)))))))))))))))
                                                                                                                                :<|> ((Named
                                                                                                                                         '("iget",
                                                                                                                                           MlsE2EIdConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for mlsE2EId"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("mlsE2EId"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  MlsE2EIdConfig))))))))))
                                                                                                                                       :<|> (Named
                                                                                                                                               '("iput",
                                                                                                                                                 MlsE2EIdConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Put config for mlsE2EId"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                          '[]
                                                                                                                                                                        :> ("teams"
                                                                                                                                                                            :> (Capture
                                                                                                                                                                                  "tid"
                                                                                                                                                                                  TeamId
                                                                                                                                                                                :> ("features"
                                                                                                                                                                                    :> ("mlsE2EId"
                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (Feature
                                                                                                                                                                                                 MlsE2EIdConfig)
                                                                                                                                                                                            :> Put
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    MlsE2EIdConfig)))))))))))))
                                                                                                                                             :<|> Named
                                                                                                                                                    '("ipatch",
                                                                                                                                                      MlsE2EIdConfig)
                                                                                                                                                    (Description
                                                                                                                                                       ""
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Patch config for mlsE2EId"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("mlsE2EId"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                                                      MlsE2EIdConfig)
                                                                                                                                                                                                 :> Patch
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         MlsE2EIdConfig)))))))))))))))
                                                                                                                                      :<|> ((Named
                                                                                                                                               '("iget",
                                                                                                                                                 MlsMigrationConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Get config for mlsMigration"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("mlsMigration"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        MlsMigrationConfig))))))))))
                                                                                                                                             :<|> (Named
                                                                                                                                                     '("iput",
                                                                                                                                                       MlsMigrationConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Put config for mlsMigration"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                          :> (CanThrowMany
                                                                                                                                                                                '[]
                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                        "tid"
                                                                                                                                                                                        TeamId
                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                          :> ("mlsMigration"
                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (Feature
                                                                                                                                                                                                       MlsMigrationConfig)
                                                                                                                                                                                                  :> Put
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          MlsMigrationConfig)))))))))))))
                                                                                                                                                   :<|> Named
                                                                                                                                                          '("ipatch",
                                                                                                                                                            MlsMigrationConfig)
                                                                                                                                                          (Description
                                                                                                                                                             ""
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Patch config for mlsMigration"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('MissingPermission
                                                                                                                                                                        'Nothing)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 TeamFeatureError
                                                                                                                                                                               :> (CanThrowMany
                                                                                                                                                                                     '[]
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> ("mlsMigration"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                                                                            MlsMigrationConfig)
                                                                                                                                                                                                       :> Patch
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               MlsMigrationConfig)))))))))))))))
                                                                                                                                            :<|> ((Named
                                                                                                                                                     '("iget",
                                                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                                                     (Description
                                                                                                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Get config for enforceFileDownloadLocation"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                                                                      :> Get
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                                   :<|> (Named
                                                                                                                                                           '("iput",
                                                                                                                                                             EnforceFileDownloadLocationConfig)
                                                                                                                                                           (Description
                                                                                                                                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Put config for enforceFileDownloadLocation"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  TeamFeatureError
                                                                                                                                                                                :> (CanThrowMany
                                                                                                                                                                                      '[]
                                                                                                                                                                                    :> ("teams"
                                                                                                                                                                                        :> (Capture
                                                                                                                                                                                              "tid"
                                                                                                                                                                                              TeamId
                                                                                                                                                                                            :> ("features"
                                                                                                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (Feature
                                                                                                                                                                                                             EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                        :> Put
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                                         :<|> Named
                                                                                                                                                                '("ipatch",
                                                                                                                                                                  EnforceFileDownloadLocationConfig)
                                                                                                                                                                (Description
                                                                                                                                                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                 :> (Summary
                                                                                                                                                                       "Patch config for enforceFileDownloadLocation"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('MissingPermission
                                                                                                                                                                              'Nothing)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       TeamFeatureError
                                                                                                                                                                                     :> (CanThrowMany
                                                                                                                                                                                           '[]
                                                                                                                                                                                         :> ("teams"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "tid"
                                                                                                                                                                                                   TeamId
                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                     :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                                                                  EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                             :> Patch
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                                  :<|> (Named
                                                                                                                                                          '("iget",
                                                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                                                          (Description
                                                                                                                                                             ""
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Get config for limitedEventFanout"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('MissingPermission
                                                                                                                                                                        'Nothing)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("teams"
                                                                                                                                                                               :> (Capture
                                                                                                                                                                                     "tid"
                                                                                                                                                                                     TeamId
                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                       :> ("limitedEventFanout"
                                                                                                                                                                                           :> Get
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   LimitedEventFanoutConfig))))))))))
                                                                                                                                                        :<|> (Named
                                                                                                                                                                '("iput",
                                                                                                                                                                  LimitedEventFanoutConfig)
                                                                                                                                                                (Description
                                                                                                                                                                   ""
                                                                                                                                                                 :> (Summary
                                                                                                                                                                       "Put config for limitedEventFanout"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('MissingPermission
                                                                                                                                                                              'Nothing)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       TeamFeatureError
                                                                                                                                                                                     :> (CanThrowMany
                                                                                                                                                                                           '[]
                                                                                                                                                                                         :> ("teams"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "tid"
                                                                                                                                                                                                   TeamId
                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                     :> ("limitedEventFanout"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               (Feature
                                                                                                                                                                                                                  LimitedEventFanoutConfig)
                                                                                                                                                                                                             :> Put
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     LimitedEventFanoutConfig)))))))))))))
                                                                                                                                                              :<|> Named
                                                                                                                                                                     '("ipatch",
                                                                                                                                                                       LimitedEventFanoutConfig)
                                                                                                                                                                     (Description
                                                                                                                                                                        ""
                                                                                                                                                                      :> (Summary
                                                                                                                                                                            "Patch config for limitedEventFanout"
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                ('MissingPermission
                                                                                                                                                                                   'Nothing)
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                                          :> (CanThrowMany
                                                                                                                                                                                                '[]
                                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                                        "tid"
                                                                                                                                                                                                        TeamId
                                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                                          :> ("limitedEventFanout"
                                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    (LockableFeaturePatch
                                                                                                                                                                                                                       LimitedEventFanoutConfig)
                                                                                                                                                                                                                  :> Patch
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                                          LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                                     :<|> (Named
                                             '("ilock", FileSharingConfig)
                                             (Summary "(Un-)lock fileSharing"
                                              :> (Description ""
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("fileSharing"
                                                                          :> (Capture
                                                                                "lockStatus"
                                                                                LockStatus
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   LockStatusResponse)))))))))
                                           :<|> (Named
                                                   '("ilock", ConferenceCallingConfig)
                                                   (Summary "(Un-)lock conferenceCalling"
                                                    :> (Description ""
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("conferenceCalling"
                                                                                :> (Capture
                                                                                      "lockStatus"
                                                                                      LockStatus
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         LockStatusResponse)))))))))
                                                 :<|> (Named
                                                         '("ilock", SelfDeletingMessagesConfig)
                                                         (Summary "(Un-)lock selfDeletingMessages"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("selfDeletingMessages"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock", GuestLinksConfig)
                                                               (Summary
                                                                  "(Un-)lock conversationGuestLinks"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("conversationGuestLinks"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock",
                                                                       SndFactorPasswordChallengeConfig)
                                                                     (Summary
                                                                        "(Un-)lock sndFactorPasswordChallenge"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("sndFactorPasswordChallenge"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock", MLSConfig)
                                                                           (Summary "(Un-)lock mls"
                                                                            :> (Description ""
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mls"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("ilock",
                                                                                   OutlookCalIntegrationConfig)
                                                                                 (Summary
                                                                                    "(Un-)lock outlookCalIntegration"
                                                                                  :> (Description ""
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("outlookCalIntegration"
                                                                                                              :> (Capture
                                                                                                                    "lockStatus"
                                                                                                                    LockStatus
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       LockStatusResponse)))))))))
                                                                               :<|> (Named
                                                                                       '("ilock",
                                                                                         MlsE2EIdConfig)
                                                                                       (Summary
                                                                                          "(Un-)lock mlsE2EId"
                                                                                        :> (Description
                                                                                              ""
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mlsE2EId"
                                                                                                                    :> (Capture
                                                                                                                          "lockStatus"
                                                                                                                          LockStatus
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             LockStatusResponse)))))))))
                                                                                     :<|> (Named
                                                                                             '("ilock",
                                                                                               MlsMigrationConfig)
                                                                                             (Summary
                                                                                                "(Un-)lock mlsMigration"
                                                                                              :> (Description
                                                                                                    ""
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mlsMigration"
                                                                                                                          :> (Capture
                                                                                                                                "lockStatus"
                                                                                                                                LockStatus
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   LockStatusResponse)))))))))
                                                                                           :<|> (Named
                                                                                                   '("ilock",
                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                   (Summary
                                                                                                      "(Un-)lock enforceFileDownloadLocation"
                                                                                                    :> (Description
                                                                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                                                :> (Capture
                                                                                                                                      "lockStatus"
                                                                                                                                      LockStatus
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         LockStatusResponse)))))))))
                                                                                                 :<|> (Named
                                                                                                         '("igetmulti",
                                                                                                           SearchVisibilityInboundConfig)
                                                                                                         (Summary
                                                                                                            "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                                          :> ("features-multi-teams"
                                                                                                              :> ("searchVisibilityInbound"
                                                                                                                  :> (ReqBody
                                                                                                                        '[JSON]
                                                                                                                        TeamFeatureNoConfigMultiRequest
                                                                                                                      :> Post
                                                                                                                           '[JSON]
                                                                                                                           (TeamFeatureNoConfigMultiResponse
                                                                                                                              SearchVisibilityInboundConfig)))))
                                                                                                       :<|> Named
                                                                                                              "feature-configs-internal"
                                                                                                              (Summary
                                                                                                                 "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                                               :> ("feature-configs"
                                                                                                                   :> (CanThrow
                                                                                                                         ('MissingPermission
                                                                                                                            'Nothing)
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> (QueryParam'
                                                                                                                                     '[Optional,
                                                                                                                                       Strict,
                                                                                                                                       Description
                                                                                                                                         "Optional user id"]
                                                                                                                                     "user_id"
                                                                                                                                     UserId
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        AllTeamFeatures))))))))))))))))))
                                    :<|> (IFederationAPI
                                          :<|> (IConversationAPI :<|> IEJPDAPI))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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-clients"
        (Summary "Get mls conversation client list"
         :> (CanThrow 'ConvNotFound
             :> ("group"
                 :> (Capture "gid" GroupId
                     :> MultiVerb
                          'GET '[JSON] '[Respond 200 "Clients" ClientList] ClientList))))
      :<|> (Named
              "guard-legalhold-policy-conflicts"
              ("guard-legalhold-policy-conflicts"
               :> (CanThrow 'MissingLegalholdConsent
                   :> (CanThrow 'MissingLegalholdConsentOldClients
                       :> (ReqBody '[JSON] GuardLegalholdPolicyConflicts
                           :> MultiVerb
                                'PUT '[JSON] '[RespondEmpty 200 "Guard Legalhold Policy"] ()))))
            :<|> (("legalhold"
                   :> ("whitelisted-teams"
                       :> (Capture "tid" TeamId
                           :> (Named
                                 "set-team-legalhold-whitelisted"
                                 (MultiVerb
                                    'PUT
                                    '[JSON]
                                    '[RespondEmpty 200 "Team Legalhold Whitelisted"]
                                    ())
                               :<|> (Named
                                       "unset-team-legalhold-whitelisted"
                                       (MultiVerb
                                          'DELETE
                                          '[JSON]
                                          '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
                                          ())
                                     :<|> Named
                                            "get-team-legalhold-whitelisted"
                                            (MultiVerb
                                               'GET
                                               '[JSON]
                                               '[RespondEmpty 404 "Team not Legalhold Whitelisted",
                                                 RespondEmpty 200 "Team Legalhold Whitelisted"]
                                               Bool))))))
                  :<|> (("teams"
                         :> (Capture "tid" TeamId
                             :> (Named
                                   "get-team-internal"
                                   (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
                                 :<|> (Named
                                         "create-binding-team"
                                         (ZUser
                                          :> (ReqBody '[JSON] BindingNewTeam
                                              :> MultiVerb
                                                   'PUT
                                                   '[JSON]
                                                   '[WithHeaders
                                                       '[Header "Location" TeamId]
                                                       TeamId
                                                       (RespondEmpty 201 "OK")]
                                                   TeamId))
                                       :<|> (Named
                                               "delete-binding-team"
                                               (CanThrow 'NoBindingTeam
                                                :> (CanThrow 'NotAOneMemberTeam
                                                    :> (CanThrow 'DeleteQueueFull
                                                        :> (CanThrow 'TeamNotFound
                                                            :> (QueryFlag "force"
                                                                :> MultiVerb
                                                                     'DELETE
                                                                     '[JSON]
                                                                     '[RespondEmpty 202 "OK"]
                                                                     ())))))
                                             :<|> (Named
                                                     "get-team-name"
                                                     ("name"
                                                      :> (CanThrow 'TeamNotFound
                                                          :> Get '[JSON] TeamName))
                                                   :<|> (Named
                                                           "update-team-status"
                                                           ("status"
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow
                                                                      'InvalidTeamStatusUpdate
                                                                    :> (ReqBody
                                                                          '[JSON] TeamStatusUpdate
                                                                        :> MultiVerb
                                                                             'PUT
                                                                             '[JSON]
                                                                             '[RespondEmpty
                                                                                 200 "OK"]
                                                                             ()))))
                                                         :<|> (("members"
                                                                :> (Named
                                                                      "unchecked-add-team-member"
                                                                      (CanThrow 'TooManyTeamMembers
                                                                       :> (CanThrow
                                                                             'TooManyTeamMembersOnTeamWithLegalhold
                                                                           :> (CanThrow
                                                                                 'TooManyTeamAdmins
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     NewTeamMember
                                                                                   :> MultiVerb
                                                                                        'POST
                                                                                        '[JSON]
                                                                                        '[RespondEmpty
                                                                                            200
                                                                                            "OK"]
                                                                                        ()))))
                                                                    :<|> (Named
                                                                            "unchecked-get-team-members"
                                                                            (QueryParam'
                                                                               '[Strict]
                                                                               "maxResults"
                                                                               (Range
                                                                                  1
                                                                                  HardTruncationLimit
                                                                                  Int32)
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  TeamMemberList)
                                                                          :<|> (Named
                                                                                  "unchecked-get-team-member"
                                                                                  (Capture
                                                                                     "uid" UserId
                                                                                   :> (CanThrow
                                                                                         'TeamMemberNotFound
                                                                                       :> Get
                                                                                            '[JSON]
                                                                                            TeamMember))
                                                                                :<|> (Named
                                                                                        "can-user-join-team"
                                                                                        ("check"
                                                                                         :> (CanThrow
                                                                                               'TooManyTeamMembersOnTeamWithLegalhold
                                                                                             :> MultiVerb
                                                                                                  'GET
                                                                                                  '[JSON]
                                                                                                  '[RespondEmpty
                                                                                                      200
                                                                                                      "User can join"]
                                                                                                  ()))
                                                                                      :<|> Named
                                                                                             "unchecked-update-team-member"
                                                                                             (CanThrow
                                                                                                'AccessDenied
                                                                                              :> (CanThrow
                                                                                                    'InvalidPermissions
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> (CanThrow
                                                                                                            'TeamMemberNotFound
                                                                                                          :> (CanThrow
                                                                                                                'TooManyTeamAdmins
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        ('MissingPermission
                                                                                                                           'Nothing)
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            NewTeamMember
                                                                                                                          :> MultiVerb
                                                                                                                               'PUT
                                                                                                                               '[JSON]
                                                                                                                               '[RespondEmpty
                                                                                                                                   200
                                                                                                                                   ""]
                                                                                                                               ())))))))))))))
                                                               :<|> (Named
                                                                       "user-is-team-owner"
                                                                       ("is-team-owner"
                                                                        :> (Capture "uid" UserId
                                                                            :> (CanThrow
                                                                                  'AccessDenied
                                                                                :> (CanThrow
                                                                                      'TeamMemberNotFound
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> MultiVerb
                                                                                             'GET
                                                                                             '[JSON]
                                                                                             '[RespondEmpty
                                                                                                 200
                                                                                                 "User is team owner"]
                                                                                             ())))))
                                                                     :<|> ("search-visibility"
                                                                           :> (Named
                                                                                 "get-search-visibility-internal"
                                                                                 (Get
                                                                                    '[JSON]
                                                                                    TeamSearchVisibilityView)
                                                                               :<|> Named
                                                                                      "set-search-visibility-internal"
                                                                                      (CanThrow
                                                                                         'TeamSearchVisibilityNotEnabled
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         TeamSearchVisibilityView
                                                                                                       :> MultiVerb
                                                                                                            'PUT
                                                                                                            '[JSON]
                                                                                                            '[RespondEmpty
                                                                                                                204
                                                                                                                "OK"]
                                                                                                            ()))))))))))))))))
                        :<|> ((Named
                                 "get-team-members"
                                 (CanThrow 'NonBindingTeam
                                  :> (CanThrow 'TeamNotFound
                                      :> ("users"
                                          :> (Capture "uid" UserId
                                              :> ("team"
                                                  :> ("members" :> Get '[JSON] TeamMemberList))))))
                               :<|> (Named
                                       "get-team-id"
                                       (CanThrow 'NonBindingTeam
                                        :> (CanThrow 'TeamNotFound
                                            :> ("users"
                                                :> (Capture "uid" UserId
                                                    :> ("team" :> Get '[JSON] TeamId)))))
                                     :<|> (Named
                                             "test-get-clients"
                                             ("test"
                                              :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
                                           :<|> (Named
                                                   "test-add-client"
                                                   ("clients"
                                                    :> (ZUser
                                                        :> (Capture "cid" ClientId
                                                            :> MultiVerb
                                                                 'POST
                                                                 '[JSON]
                                                                 '[RespondEmpty 200 "OK"]
                                                                 ())))
                                                 :<|> (Named
                                                         "test-delete-client"
                                                         ("clients"
                                                          :> (ZUser
                                                              :> (Capture "cid" ClientId
                                                                  :> MultiVerb
                                                                       'DELETE
                                                                       '[JSON]
                                                                       '[RespondEmpty 200 "OK"]
                                                                       ())))
                                                       :<|> (Named
                                                               "add-service"
                                                               ("services"
                                                                :> (ReqBody '[JSON] Service
                                                                    :> MultiVerb
                                                                         'POST
                                                                         '[JSON]
                                                                         '[RespondEmpty 200 "OK"]
                                                                         ()))
                                                             :<|> (Named
                                                                     "delete-service"
                                                                     ("services"
                                                                      :> (ReqBody '[JSON] ServiceRef
                                                                          :> MultiVerb
                                                                               'DELETE
                                                                               '[JSON]
                                                                               '[RespondEmpty
                                                                                   200 "OK"]
                                                                               ()))
                                                                   :<|> (Named
                                                                           "i-add-bot"
                                                                           (CanThrow
                                                                              ('ActionDenied
                                                                                 'AddConversationMember)
                                                                            :> (CanThrow
                                                                                  'ConvNotFound
                                                                                :> (CanThrow
                                                                                      'InvalidOperation
                                                                                    :> (CanThrow
                                                                                          'TooManyMembers
                                                                                        :> ("bots"
                                                                                            :> (ZLocalUser
                                                                                                :> (ZConn
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          AddBot
                                                                                                        :> Post
                                                                                                             '[JSON]
                                                                                                             Event))))))))
                                                                         :<|> (Named
                                                                                 "delete-bot"
                                                                                 (CanThrow
                                                                                    'ConvNotFound
                                                                                  :> (CanThrow
                                                                                        ('ActionDenied
                                                                                           'RemoveConversationMember)
                                                                                      :> ("bots"
                                                                                          :> (ZLocalUser
                                                                                              :> (ZOptConn
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        RemoveBot
                                                                                                      :> MultiVerb
                                                                                                           'DELETE
                                                                                                           '[JSON]
                                                                                                           (UpdateResponses
                                                                                                              "Bot not found"
                                                                                                              "Bot deleted"
                                                                                                              Event)
                                                                                                           (UpdateResult
                                                                                                              Event)))))))
                                                                               :<|> (Named
                                                                                       "put-custom-backend"
                                                                                       ("custom-backend"
                                                                                        :> ("by-domain"
                                                                                            :> (Capture
                                                                                                  "domain"
                                                                                                  Domain
                                                                                                :> (ReqBody
                                                                                                      '[JSON]
                                                                                                      CustomBackend
                                                                                                    :> MultiVerb
                                                                                                         'PUT
                                                                                                         '[JSON]
                                                                                                         '[RespondEmpty
                                                                                                             201
                                                                                                             "OK"]
                                                                                                         ()))))
                                                                                     :<|> Named
                                                                                            "delete-custom-backend"
                                                                                            ("custom-backend"
                                                                                             :> ("by-domain"
                                                                                                 :> (Capture
                                                                                                       "domain"
                                                                                                       Domain
                                                                                                     :> MultiVerb
                                                                                                          'DELETE
                                                                                                          '[JSON]
                                                                                                          '[RespondEmpty
                                                                                                              200
                                                                                                              "OK"]
                                                                                                          ())))))))))))))
                              :<|> (Named
                                      "upsert-one2one"
                                      (Summary "Create or Update a connect or one2one conversation."
                                       :> ("conversations"
                                           :> ("one2one"
                                               :> ("upsert"
                                                   :> (ReqBody
                                                         '[JSON] UpsertOne2OneConversationRequest
                                                       :> MultiVerb
                                                            'POST
                                                            '[JSON]
                                                            '[RespondEmpty
                                                                200 "Upsert One2One Policy"]
                                                            ())))))
                                    :<|> ((((Named
                                               '("iget", LegalholdConfig)
                                               (Description ""
                                                :> (Summary "Get config for legalhold"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("legalhold"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        LegalholdConfig))))))))))
                                             :<|> (Named
                                                     '("iput", LegalholdConfig)
                                                     (Description ""
                                                      :> (Summary "Put config for legalhold"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany
                                                                                '[ 'ActionDenied
                                                                                     'RemoveConversationMember,
                                                                                   'CannotEnableLegalHoldServiceLargeTeam,
                                                                                   'LegalHoldNotEnabled,
                                                                                   'LegalHoldDisableUnimplemented,
                                                                                   'LegalHoldServiceNotRegistered,
                                                                                   'UserLegalHoldIllegalOperation,
                                                                                   'LegalHoldCouldNotBlockConnections]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("legalhold"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (Feature
                                                                                                       LegalholdConfig)
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          LegalholdConfig)))))))))))))
                                                   :<|> Named
                                                          '("ipatch", LegalholdConfig)
                                                          (Description ""
                                                           :> (Summary "Patch config for legalhold"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany
                                                                                     '[ 'ActionDenied
                                                                                          'RemoveConversationMember,
                                                                                        'CannotEnableLegalHoldServiceLargeTeam,
                                                                                        'LegalHoldNotEnabled,
                                                                                        'LegalHoldDisableUnimplemented,
                                                                                        'LegalHoldServiceNotRegistered,
                                                                                        'UserLegalHoldIllegalOperation,
                                                                                        'LegalHoldCouldNotBlockConnections]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("legalhold"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (LockableFeaturePatch
                                                                                                            LegalholdConfig)
                                                                                                       :> Patch
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               LegalholdConfig)))))))))))))))
                                            :<|> ((Named
                                                     '("iget", SSOConfig)
                                                     (Description ""
                                                      :> (Summary "Get config for sso"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("sso"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              SSOConfig))))))))))
                                                   :<|> (Named
                                                           '("iput", SSOConfig)
                                                           (Description ""
                                                            :> (Summary "Put config for sso"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("sso"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             SSOConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SSOConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch", SSOConfig)
                                                                (Description ""
                                                                 :> (Summary "Patch config for sso"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("sso"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  SSOConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     SSOConfig)))))))))))))))
                                                  :<|> ((Named
                                                           '("iget",
                                                             SearchVisibilityAvailableConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Get config for searchVisibility"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("searchVisibility"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    SearchVisibilityAvailableConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput",
                                                                   SearchVisibilityAvailableConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Put config for searchVisibility"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("searchVisibility"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   SearchVisibilityAvailableConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      SearchVisibilityAvailableConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch",
                                                                        SearchVisibilityAvailableConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for searchVisibility"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("searchVisibility"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        SearchVisibilityAvailableConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           SearchVisibilityAvailableConfig)))))))))))))))
                                                        :<|> ((Named
                                                                 '("iget",
                                                                   SearchVisibilityInboundConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Get config for searchVisibilityInbound"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("searchVisibilityInbound"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          SearchVisibilityInboundConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput",
                                                                         SearchVisibilityInboundConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for searchVisibilityInbound"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("searchVisibilityInbound"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         SearchVisibilityInboundConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            SearchVisibilityInboundConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch",
                                                                              SearchVisibilityInboundConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for searchVisibilityInbound"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("searchVisibilityInbound"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              SearchVisibilityInboundConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 SearchVisibilityInboundConfig)))))))))))))))
                                                              :<|> ((Named
                                                                       '("iget",
                                                                         ValidateSAMLEmailsConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for validateSAMLemails"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("validateSAMLemails"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                ValidateSAMLEmailsConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               ValidateSAMLEmailsConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for validateSAMLemails"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("validateSAMLemails"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               ValidateSAMLEmailsConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  ValidateSAMLEmailsConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    ValidateSAMLEmailsConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for validateSAMLemails"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("validateSAMLemails"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    ValidateSAMLEmailsConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       ValidateSAMLEmailsConfig)))))))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               DigitalSignaturesConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for digitalSignatures"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("digitalSignatures"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      DigitalSignaturesConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     DigitalSignaturesConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for digitalSignatures"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("digitalSignatures"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     DigitalSignaturesConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        DigitalSignaturesConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          DigitalSignaturesConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for digitalSignatures"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("digitalSignatures"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          DigitalSignaturesConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             DigitalSignaturesConfig)))))))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     AppLockConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for appLock"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("appLock"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            AppLockConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           AppLockConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for appLock"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("appLock"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           AppLockConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              AppLockConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                AppLockConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for appLock"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("appLock"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                AppLockConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   AppLockConfig)))))))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           FileSharingConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for fileSharing"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("fileSharing"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  FileSharingConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 FileSharingConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for fileSharing"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("fileSharing"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 FileSharingConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    FileSharingConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      FileSharingConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for fileSharing"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("fileSharing"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      FileSharingConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         FileSharingConfig)))))))))))))))
                                                                                      :<|> (Named
                                                                                              '("iget",
                                                                                                ClassifiedDomainsConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Get config for classifiedDomains"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("classifiedDomains"
                                                                                                                               :> Get
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       ClassifiedDomainsConfig))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       ConferenceCallingConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for conferenceCalling"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("conferenceCalling"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              ConferenceCallingConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             ConferenceCallingConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for conferenceCalling"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("conferenceCalling"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             ConferenceCallingConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                ConferenceCallingConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  ConferenceCallingConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for conferenceCalling"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("conferenceCalling"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  ConferenceCallingConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     ConferenceCallingConfig)))))))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             SelfDeletingMessagesConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for selfDeletingMessages"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("selfDeletingMessages"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    SelfDeletingMessagesConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   SelfDeletingMessagesConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for selfDeletingMessages"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("selfDeletingMessages"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   SelfDeletingMessagesConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      SelfDeletingMessagesConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        SelfDeletingMessagesConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for selfDeletingMessages"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("selfDeletingMessages"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        SelfDeletingMessagesConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           SelfDeletingMessagesConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   GuestLinksConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for conversationGuestLinks"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("conversationGuestLinks"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          GuestLinksConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         GuestLinksConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for conversationGuestLinks"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("conversationGuestLinks"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         GuestLinksConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            GuestLinksConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              GuestLinksConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for conversationGuestLinks"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              GuestLinksConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 GuestLinksConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         SndFactorPasswordChallengeConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for sndFactorPasswordChallenge"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("sndFactorPasswordChallenge"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                SndFactorPasswordChallengeConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               SndFactorPasswordChallengeConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for sndFactorPasswordChallenge"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("sndFactorPasswordChallenge"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               SndFactorPasswordChallengeConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  SndFactorPasswordChallengeConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    SndFactorPasswordChallengeConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for sndFactorPasswordChallenge"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    SndFactorPasswordChallengeConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               MLSConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for mls"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("mls"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      MLSConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     MLSConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for mls"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("mls"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     MLSConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        MLSConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          MLSConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for mls"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("mls"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          MLSConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             MLSConfig)))))))))))))))
                                                                                                                          :<|> ((Named
                                                                                                                                   '("iget",
                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                                                 :<|> (Named
                                                                                                                                         '("iput",
                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Feature
                                                                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                      :> Put
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                                                       :<|> Named
                                                                                                                                              '("ipatch",
                                                                                                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                                                :<|> ((Named
                                                                                                                                         '("iget",
                                                                                                                                           OutlookCalIntegrationConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for outlookCalIntegration"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("outlookCalIntegration"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  OutlookCalIntegrationConfig))))))))))
                                                                                                                                       :<|> (Named
                                                                                                                                               '("iput",
                                                                                                                                                 OutlookCalIntegrationConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Put config for outlookCalIntegration"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                          '[]
                                                                                                                                                                        :> ("teams"
                                                                                                                                                                            :> (Capture
                                                                                                                                                                                  "tid"
                                                                                                                                                                                  TeamId
                                                                                                                                                                                :> ("features"
                                                                                                                                                                                    :> ("outlookCalIntegration"
                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (Feature
                                                                                                                                                                                                 OutlookCalIntegrationConfig)
                                                                                                                                                                                            :> Put
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    OutlookCalIntegrationConfig)))))))))))))
                                                                                                                                             :<|> Named
                                                                                                                                                    '("ipatch",
                                                                                                                                                      OutlookCalIntegrationConfig)
                                                                                                                                                    (Description
                                                                                                                                                       ""
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Patch config for outlookCalIntegration"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("outlookCalIntegration"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                                                      OutlookCalIntegrationConfig)
                                                                                                                                                                                                 :> Patch
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         OutlookCalIntegrationConfig)))))))))))))))
                                                                                                                                      :<|> ((Named
                                                                                                                                               '("iget",
                                                                                                                                                 MlsE2EIdConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Get config for mlsE2EId"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("mlsE2EId"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        MlsE2EIdConfig))))))))))
                                                                                                                                             :<|> (Named
                                                                                                                                                     '("iput",
                                                                                                                                                       MlsE2EIdConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Put config for mlsE2EId"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                          :> (CanThrowMany
                                                                                                                                                                                '[]
                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                        "tid"
                                                                                                                                                                                        TeamId
                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                          :> ("mlsE2EId"
                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (Feature
                                                                                                                                                                                                       MlsE2EIdConfig)
                                                                                                                                                                                                  :> Put
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          MlsE2EIdConfig)))))))))))))
                                                                                                                                                   :<|> Named
                                                                                                                                                          '("ipatch",
                                                                                                                                                            MlsE2EIdConfig)
                                                                                                                                                          (Description
                                                                                                                                                             ""
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Patch config for mlsE2EId"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('MissingPermission
                                                                                                                                                                        'Nothing)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 TeamFeatureError
                                                                                                                                                                               :> (CanThrowMany
                                                                                                                                                                                     '[]
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> ("mlsE2EId"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                                                                            MlsE2EIdConfig)
                                                                                                                                                                                                       :> Patch
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               MlsE2EIdConfig)))))))))))))))
                                                                                                                                            :<|> ((Named
                                                                                                                                                     '("iget",
                                                                                                                                                       MlsMigrationConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Get config for mlsMigration"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("mlsMigration"
                                                                                                                                                                                      :> Get
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              MlsMigrationConfig))))))))))
                                                                                                                                                   :<|> (Named
                                                                                                                                                           '("iput",
                                                                                                                                                             MlsMigrationConfig)
                                                                                                                                                           (Description
                                                                                                                                                              ""
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Put config for mlsMigration"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  TeamFeatureError
                                                                                                                                                                                :> (CanThrowMany
                                                                                                                                                                                      '[]
                                                                                                                                                                                    :> ("teams"
                                                                                                                                                                                        :> (Capture
                                                                                                                                                                                              "tid"
                                                                                                                                                                                              TeamId
                                                                                                                                                                                            :> ("features"
                                                                                                                                                                                                :> ("mlsMigration"
                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (Feature
                                                                                                                                                                                                             MlsMigrationConfig)
                                                                                                                                                                                                        :> Put
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                MlsMigrationConfig)))))))))))))
                                                                                                                                                         :<|> Named
                                                                                                                                                                '("ipatch",
                                                                                                                                                                  MlsMigrationConfig)
                                                                                                                                                                (Description
                                                                                                                                                                   ""
                                                                                                                                                                 :> (Summary
                                                                                                                                                                       "Patch config for mlsMigration"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('MissingPermission
                                                                                                                                                                              'Nothing)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       TeamFeatureError
                                                                                                                                                                                     :> (CanThrowMany
                                                                                                                                                                                           '[]
                                                                                                                                                                                         :> ("teams"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "tid"
                                                                                                                                                                                                   TeamId
                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                     :> ("mlsMigration"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                                                                  MlsMigrationConfig)
                                                                                                                                                                                                             :> Patch
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     MlsMigrationConfig)))))))))))))))
                                                                                                                                                  :<|> ((Named
                                                                                                                                                           '("iget",
                                                                                                                                                             EnforceFileDownloadLocationConfig)
                                                                                                                                                           (Description
                                                                                                                                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Get config for enforceFileDownloadLocation"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                :> (Capture
                                                                                                                                                                                      "tid"
                                                                                                                                                                                      TeamId
                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                        :> ("enforceFileDownloadLocation"
                                                                                                                                                                                            :> Get
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                                         :<|> (Named
                                                                                                                                                                 '("iput",
                                                                                                                                                                   EnforceFileDownloadLocationConfig)
                                                                                                                                                                 (Description
                                                                                                                                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                  :> (Summary
                                                                                                                                                                        "Put config for enforceFileDownloadLocation"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            ('MissingPermission
                                                                                                                                                                               'Nothing)
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        TeamFeatureError
                                                                                                                                                                                      :> (CanThrowMany
                                                                                                                                                                                            '[]
                                                                                                                                                                                          :> ("teams"
                                                                                                                                                                                              :> (Capture
                                                                                                                                                                                                    "tid"
                                                                                                                                                                                                    TeamId
                                                                                                                                                                                                  :> ("features"
                                                                                                                                                                                                      :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (Feature
                                                                                                                                                                                                                   EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                              :> Put
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                                      EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                                               :<|> Named
                                                                                                                                                                      '("ipatch",
                                                                                                                                                                        EnforceFileDownloadLocationConfig)
                                                                                                                                                                      (Description
                                                                                                                                                                         "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                       :> (Summary
                                                                                                                                                                             "Patch config for enforceFileDownloadLocation"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('MissingPermission
                                                                                                                                                                                    'Nothing)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             TeamFeatureError
                                                                                                                                                                                           :> (CanThrowMany
                                                                                                                                                                                                 '[]
                                                                                                                                                                                               :> ("teams"
                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                         "tid"
                                                                                                                                                                                                         TeamId
                                                                                                                                                                                                       :> ("features"
                                                                                                                                                                                                           :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                                                                        EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                                   :> Patch
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                           EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                                        :<|> (Named
                                                                                                                                                                '("iget",
                                                                                                                                                                  LimitedEventFanoutConfig)
                                                                                                                                                                (Description
                                                                                                                                                                   ""
                                                                                                                                                                 :> (Summary
                                                                                                                                                                       "Get config for limitedEventFanout"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('MissingPermission
                                                                                                                                                                              'Nothing)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("teams"
                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                           "tid"
                                                                                                                                                                                           TeamId
                                                                                                                                                                                         :> ("features"
                                                                                                                                                                                             :> ("limitedEventFanout"
                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         LimitedEventFanoutConfig))))))))))
                                                                                                                                                              :<|> (Named
                                                                                                                                                                      '("iput",
                                                                                                                                                                        LimitedEventFanoutConfig)
                                                                                                                                                                      (Description
                                                                                                                                                                         ""
                                                                                                                                                                       :> (Summary
                                                                                                                                                                             "Put config for limitedEventFanout"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('MissingPermission
                                                                                                                                                                                    'Nothing)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             TeamFeatureError
                                                                                                                                                                                           :> (CanThrowMany
                                                                                                                                                                                                 '[]
                                                                                                                                                                                               :> ("teams"
                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                         "tid"
                                                                                                                                                                                                         TeamId
                                                                                                                                                                                                       :> ("features"
                                                                                                                                                                                                           :> ("limitedEventFanout"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     (Feature
                                                                                                                                                                                                                        LimitedEventFanoutConfig)
                                                                                                                                                                                                                   :> Put
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                           LimitedEventFanoutConfig)))))))))))))
                                                                                                                                                                    :<|> Named
                                                                                                                                                                           '("ipatch",
                                                                                                                                                                             LimitedEventFanoutConfig)
                                                                                                                                                                           (Description
                                                                                                                                                                              ""
                                                                                                                                                                            :> (Summary
                                                                                                                                                                                  "Patch config for limitedEventFanout"
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                                         'Nothing)
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  TeamFeatureError
                                                                                                                                                                                                :> (CanThrowMany
                                                                                                                                                                                                      '[]
                                                                                                                                                                                                    :> ("teams"
                                                                                                                                                                                                        :> (Capture
                                                                                                                                                                                                              "tid"
                                                                                                                                                                                                              TeamId
                                                                                                                                                                                                            :> ("features"
                                                                                                                                                                                                                :> ("limitedEventFanout"
                                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          (LockableFeaturePatch
                                                                                                                                                                                                                             LimitedEventFanoutConfig)
                                                                                                                                                                                                                        :> Patch
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                                LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                                           :<|> (Named
                                                   '("ilock", FileSharingConfig)
                                                   (Summary "(Un-)lock fileSharing"
                                                    :> (Description ""
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("fileSharing"
                                                                                :> (Capture
                                                                                      "lockStatus"
                                                                                      LockStatus
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         LockStatusResponse)))))))))
                                                 :<|> (Named
                                                         '("ilock", ConferenceCallingConfig)
                                                         (Summary "(Un-)lock conferenceCalling"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("conferenceCalling"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock",
                                                                 SelfDeletingMessagesConfig)
                                                               (Summary
                                                                  "(Un-)lock selfDeletingMessages"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("selfDeletingMessages"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock", GuestLinksConfig)
                                                                     (Summary
                                                                        "(Un-)lock conversationGuestLinks"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("conversationGuestLinks"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock",
                                                                             SndFactorPasswordChallengeConfig)
                                                                           (Summary
                                                                              "(Un-)lock sndFactorPasswordChallenge"
                                                                            :> (Description ""
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("sndFactorPasswordChallenge"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("ilock",
                                                                                   MLSConfig)
                                                                                 (Summary
                                                                                    "(Un-)lock mls"
                                                                                  :> (Description ""
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mls"
                                                                                                              :> (Capture
                                                                                                                    "lockStatus"
                                                                                                                    LockStatus
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       LockStatusResponse)))))))))
                                                                               :<|> (Named
                                                                                       '("ilock",
                                                                                         OutlookCalIntegrationConfig)
                                                                                       (Summary
                                                                                          "(Un-)lock outlookCalIntegration"
                                                                                        :> (Description
                                                                                              ""
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("outlookCalIntegration"
                                                                                                                    :> (Capture
                                                                                                                          "lockStatus"
                                                                                                                          LockStatus
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             LockStatusResponse)))))))))
                                                                                     :<|> (Named
                                                                                             '("ilock",
                                                                                               MlsE2EIdConfig)
                                                                                             (Summary
                                                                                                "(Un-)lock mlsE2EId"
                                                                                              :> (Description
                                                                                                    ""
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mlsE2EId"
                                                                                                                          :> (Capture
                                                                                                                                "lockStatus"
                                                                                                                                LockStatus
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   LockStatusResponse)))))))))
                                                                                           :<|> (Named
                                                                                                   '("ilock",
                                                                                                     MlsMigrationConfig)
                                                                                                   (Summary
                                                                                                      "(Un-)lock mlsMigration"
                                                                                                    :> (Description
                                                                                                          ""
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mlsMigration"
                                                                                                                                :> (Capture
                                                                                                                                      "lockStatus"
                                                                                                                                      LockStatus
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         LockStatusResponse)))))))))
                                                                                                 :<|> (Named
                                                                                                         '("ilock",
                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                         (Summary
                                                                                                            "(Un-)lock enforceFileDownloadLocation"
                                                                                                          :> (Description
                                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                      :> (Capture
                                                                                                                                            "lockStatus"
                                                                                                                                            LockStatus
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               LockStatusResponse)))))))))
                                                                                                       :<|> (Named
                                                                                                               '("igetmulti",
                                                                                                                 SearchVisibilityInboundConfig)
                                                                                                               (Summary
                                                                                                                  "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                                                :> ("features-multi-teams"
                                                                                                                    :> ("searchVisibilityInbound"
                                                                                                                        :> (ReqBody
                                                                                                                              '[JSON]
                                                                                                                              TeamFeatureNoConfigMultiRequest
                                                                                                                            :> Post
                                                                                                                                 '[JSON]
                                                                                                                                 (TeamFeatureNoConfigMultiResponse
                                                                                                                                    SearchVisibilityInboundConfig)))))
                                                                                                             :<|> Named
                                                                                                                    "feature-configs-internal"
                                                                                                                    (Summary
                                                                                                                       "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> (CanThrow
                                                                                                                               ('MissingPermission
                                                                                                                                  'Nothing)
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotATeamMember
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TeamNotFound
                                                                                                                                     :> (QueryParam'
                                                                                                                                           '[Optional,
                                                                                                                                             Strict,
                                                                                                                                             Description
                                                                                                                                               "Optional user id"]
                                                                                                                                           "user_id"
                                                                                                                                           UserId
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              AllTeamFeatures))))))))))))))))))
                                          :<|> (IFederationAPI
                                                :<|> (IConversationAPI :<|> IEJPDAPI)))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"guard-legalhold-policy-conflicts" ServerT
  ("guard-legalhold-policy-conflicts"
   :> (CanThrow 'MissingLegalholdConsent
       :> (CanThrow 'MissingLegalholdConsentOldClients
           :> (ReqBody '[JSON] GuardLegalholdPolicyConflicts
               :> MultiVerb
                    'PUT '[JSON] '[RespondEmpty 200 "Guard Legalhold Policy"] ()))))
  (Sem
     (Append
        (DeclaredErrorEffects
           ("guard-legalhold-policy-conflicts"
            :> (CanThrow 'MissingLegalholdConsent
                :> (CanThrow 'MissingLegalholdConsentOldClients
                    :> (ReqBody '[JSON] GuardLegalholdPolicyConflicts
                        :> MultiVerb
                             'PUT '[JSON] '[RespondEmpty 200 "Guard Legalhold Policy"] ())))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
GuardLegalholdPolicyConflicts
-> Sem
     '[Error (Tagged 'MissingLegalholdConsent ()),
       Error (Tagged 'MissingLegalholdConsentOldClients ()), BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 BrigAccess r, Member (Input Opts) r, Member TeamStore r,
 Member (Logger (Msg -> Msg)) r,
 Member (Error (Tagged 'MissingLegalholdConsent ())) r,
 Member (Error (Tagged 'MissingLegalholdConsentOldClients ())) r) =>
GuardLegalholdPolicyConflicts -> Sem r ()
guardLegalholdPolicyConflictsH
      API
  (Named
     "guard-legalhold-policy-conflicts"
     ("guard-legalhold-policy-conflicts"
      :> (CanThrow 'MissingLegalholdConsent
          :> (CanThrow 'MissingLegalholdConsentOldClients
              :> (ReqBody '[JSON] GuardLegalholdPolicyConflicts
                  :> MultiVerb
                       'PUT '[JSON] '[RespondEmpty 200 "Guard Legalhold Policy"] ())))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     (("legalhold"
       :> ("whitelisted-teams"
           :> (Capture "tid" TeamId
               :> (Named
                     "set-team-legalhold-whitelisted"
                     (MultiVerb
                        'PUT '[JSON] '[RespondEmpty 200 "Team Legalhold Whitelisted"] ())
                   :<|> (Named
                           "unset-team-legalhold-whitelisted"
                           (MultiVerb
                              'DELETE
                              '[JSON]
                              '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
                              ())
                         :<|> Named
                                "get-team-legalhold-whitelisted"
                                (MultiVerb
                                   'GET
                                   '[JSON]
                                   '[RespondEmpty 404 "Team not Legalhold Whitelisted",
                                     RespondEmpty 200 "Team Legalhold Whitelisted"]
                                   Bool))))))
      :<|> (("teams"
             :> (Capture "tid" TeamId
                 :> (Named
                       "get-team-internal"
                       (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
                     :<|> (Named
                             "create-binding-team"
                             (ZUser
                              :> (ReqBody '[JSON] BindingNewTeam
                                  :> MultiVerb
                                       'PUT
                                       '[JSON]
                                       '[WithHeaders
                                           '[Header "Location" TeamId]
                                           TeamId
                                           (RespondEmpty 201 "OK")]
                                       TeamId))
                           :<|> (Named
                                   "delete-binding-team"
                                   (CanThrow 'NoBindingTeam
                                    :> (CanThrow 'NotAOneMemberTeam
                                        :> (CanThrow 'DeleteQueueFull
                                            :> (CanThrow 'TeamNotFound
                                                :> (QueryFlag "force"
                                                    :> MultiVerb
                                                         'DELETE
                                                         '[JSON]
                                                         '[RespondEmpty 202 "OK"]
                                                         ())))))
                                 :<|> (Named
                                         "get-team-name"
                                         ("name"
                                          :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
                                       :<|> (Named
                                               "update-team-status"
                                               ("status"
                                                :> (CanThrow 'TeamNotFound
                                                    :> (CanThrow 'InvalidTeamStatusUpdate
                                                        :> (ReqBody '[JSON] TeamStatusUpdate
                                                            :> MultiVerb
                                                                 'PUT
                                                                 '[JSON]
                                                                 '[RespondEmpty 200 "OK"]
                                                                 ()))))
                                             :<|> (("members"
                                                    :> (Named
                                                          "unchecked-add-team-member"
                                                          (CanThrow 'TooManyTeamMembers
                                                           :> (CanThrow
                                                                 'TooManyTeamMembersOnTeamWithLegalhold
                                                               :> (CanThrow 'TooManyTeamAdmins
                                                                   :> (ReqBody '[JSON] NewTeamMember
                                                                       :> MultiVerb
                                                                            'POST
                                                                            '[JSON]
                                                                            '[RespondEmpty 200 "OK"]
                                                                            ()))))
                                                        :<|> (Named
                                                                "unchecked-get-team-members"
                                                                (QueryParam'
                                                                   '[Strict]
                                                                   "maxResults"
                                                                   (Range
                                                                      1 HardTruncationLimit Int32)
                                                                 :> Get '[JSON] TeamMemberList)
                                                              :<|> (Named
                                                                      "unchecked-get-team-member"
                                                                      (Capture "uid" UserId
                                                                       :> (CanThrow
                                                                             'TeamMemberNotFound
                                                                           :> Get
                                                                                '[JSON] TeamMember))
                                                                    :<|> (Named
                                                                            "can-user-join-team"
                                                                            ("check"
                                                                             :> (CanThrow
                                                                                   'TooManyTeamMembersOnTeamWithLegalhold
                                                                                 :> MultiVerb
                                                                                      'GET
                                                                                      '[JSON]
                                                                                      '[RespondEmpty
                                                                                          200
                                                                                          "User can join"]
                                                                                      ()))
                                                                          :<|> Named
                                                                                 "unchecked-update-team-member"
                                                                                 (CanThrow
                                                                                    'AccessDenied
                                                                                  :> (CanThrow
                                                                                        'InvalidPermissions
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> (CanThrow
                                                                                                'TeamMemberNotFound
                                                                                              :> (CanThrow
                                                                                                    'TooManyTeamAdmins
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            ('MissingPermission
                                                                                                               'Nothing)
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                NewTeamMember
                                                                                                              :> MultiVerb
                                                                                                                   'PUT
                                                                                                                   '[JSON]
                                                                                                                   '[RespondEmpty
                                                                                                                       200
                                                                                                                       ""]
                                                                                                                   ())))))))))))))
                                                   :<|> (Named
                                                           "user-is-team-owner"
                                                           ("is-team-owner"
                                                            :> (Capture "uid" UserId
                                                                :> (CanThrow 'AccessDenied
                                                                    :> (CanThrow 'TeamMemberNotFound
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> MultiVerb
                                                                                 'GET
                                                                                 '[JSON]
                                                                                 '[RespondEmpty
                                                                                     200
                                                                                     "User is team owner"]
                                                                                 ())))))
                                                         :<|> ("search-visibility"
                                                               :> (Named
                                                                     "get-search-visibility-internal"
                                                                     (Get
                                                                        '[JSON]
                                                                        TeamSearchVisibilityView)
                                                                   :<|> Named
                                                                          "set-search-visibility-internal"
                                                                          (CanThrow
                                                                             'TeamSearchVisibilityNotEnabled
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             TeamSearchVisibilityView
                                                                                           :> MultiVerb
                                                                                                'PUT
                                                                                                '[JSON]
                                                                                                '[RespondEmpty
                                                                                                    204
                                                                                                    "OK"]
                                                                                                ()))))))))))))))))
            :<|> ((Named
                     "get-team-members"
                     (CanThrow 'NonBindingTeam
                      :> (CanThrow 'TeamNotFound
                          :> ("users"
                              :> (Capture "uid" UserId
                                  :> ("team" :> ("members" :> Get '[JSON] TeamMemberList))))))
                   :<|> (Named
                           "get-team-id"
                           (CanThrow 'NonBindingTeam
                            :> (CanThrow 'TeamNotFound
                                :> ("users"
                                    :> (Capture "uid" UserId :> ("team" :> Get '[JSON] TeamId)))))
                         :<|> (Named
                                 "test-get-clients"
                                 ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
                               :<|> (Named
                                       "test-add-client"
                                       ("clients"
                                        :> (ZUser
                                            :> (Capture "cid" ClientId
                                                :> MultiVerb
                                                     'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
                                     :<|> (Named
                                             "test-delete-client"
                                             ("clients"
                                              :> (ZUser
                                                  :> (Capture "cid" ClientId
                                                      :> MultiVerb
                                                           'DELETE
                                                           '[JSON]
                                                           '[RespondEmpty 200 "OK"]
                                                           ())))
                                           :<|> (Named
                                                   "add-service"
                                                   ("services"
                                                    :> (ReqBody '[JSON] Service
                                                        :> MultiVerb
                                                             'POST
                                                             '[JSON]
                                                             '[RespondEmpty 200 "OK"]
                                                             ()))
                                                 :<|> (Named
                                                         "delete-service"
                                                         ("services"
                                                          :> (ReqBody '[JSON] ServiceRef
                                                              :> MultiVerb
                                                                   'DELETE
                                                                   '[JSON]
                                                                   '[RespondEmpty 200 "OK"]
                                                                   ()))
                                                       :<|> (Named
                                                               "i-add-bot"
                                                               (CanThrow
                                                                  ('ActionDenied
                                                                     'AddConversationMember)
                                                                :> (CanThrow 'ConvNotFound
                                                                    :> (CanThrow 'InvalidOperation
                                                                        :> (CanThrow 'TooManyMembers
                                                                            :> ("bots"
                                                                                :> (ZLocalUser
                                                                                    :> (ZConn
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              AddBot
                                                                                            :> Post
                                                                                                 '[JSON]
                                                                                                 Event))))))))
                                                             :<|> (Named
                                                                     "delete-bot"
                                                                     (CanThrow 'ConvNotFound
                                                                      :> (CanThrow
                                                                            ('ActionDenied
                                                                               'RemoveConversationMember)
                                                                          :> ("bots"
                                                                              :> (ZLocalUser
                                                                                  :> (ZOptConn
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            RemoveBot
                                                                                          :> MultiVerb
                                                                                               'DELETE
                                                                                               '[JSON]
                                                                                               (UpdateResponses
                                                                                                  "Bot not found"
                                                                                                  "Bot deleted"
                                                                                                  Event)
                                                                                               (UpdateResult
                                                                                                  Event)))))))
                                                                   :<|> (Named
                                                                           "put-custom-backend"
                                                                           ("custom-backend"
                                                                            :> ("by-domain"
                                                                                :> (Capture
                                                                                      "domain"
                                                                                      Domain
                                                                                    :> (ReqBody
                                                                                          '[JSON]
                                                                                          CustomBackend
                                                                                        :> MultiVerb
                                                                                             'PUT
                                                                                             '[JSON]
                                                                                             '[RespondEmpty
                                                                                                 201
                                                                                                 "OK"]
                                                                                             ()))))
                                                                         :<|> Named
                                                                                "delete-custom-backend"
                                                                                ("custom-backend"
                                                                                 :> ("by-domain"
                                                                                     :> (Capture
                                                                                           "domain"
                                                                                           Domain
                                                                                         :> MultiVerb
                                                                                              'DELETE
                                                                                              '[JSON]
                                                                                              '[RespondEmpty
                                                                                                  200
                                                                                                  "OK"]
                                                                                              ())))))))))))))
                  :<|> (Named
                          "upsert-one2one"
                          (Summary "Create or Update a connect or one2one conversation."
                           :> ("conversations"
                               :> ("one2one"
                                   :> ("upsert"
                                       :> (ReqBody '[JSON] UpsertOne2OneConversationRequest
                                           :> MultiVerb
                                                'POST
                                                '[JSON]
                                                '[RespondEmpty 200 "Upsert One2One Policy"]
                                                ())))))
                        :<|> ((((Named
                                   '("iget", LegalholdConfig)
                                   (Description ""
                                    :> (Summary "Get config for legalhold"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("legalhold"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            LegalholdConfig))))))))))
                                 :<|> (Named
                                         '("iput", LegalholdConfig)
                                         (Description ""
                                          :> (Summary "Put config for legalhold"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow TeamFeatureError
                                                              :> (CanThrowMany
                                                                    '[ 'ActionDenied
                                                                         'RemoveConversationMember,
                                                                       'CannotEnableLegalHoldServiceLargeTeam,
                                                                       'LegalHoldNotEnabled,
                                                                       'LegalHoldDisableUnimplemented,
                                                                       'LegalHoldServiceNotRegistered,
                                                                       'UserLegalHoldIllegalOperation,
                                                                       'LegalHoldCouldNotBlockConnections]
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("legalhold"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        (Feature
                                                                                           LegalholdConfig)
                                                                                      :> Put
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              LegalholdConfig)))))))))))))
                                       :<|> Named
                                              '("ipatch", LegalholdConfig)
                                              (Description ""
                                               :> (Summary "Patch config for legalhold"
                                                   :> (CanThrow ('MissingPermission 'Nothing)
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany
                                                                         '[ 'ActionDenied
                                                                              'RemoveConversationMember,
                                                                            'CannotEnableLegalHoldServiceLargeTeam,
                                                                            'LegalHoldNotEnabled,
                                                                            'LegalHoldDisableUnimplemented,
                                                                            'LegalHoldServiceNotRegistered,
                                                                            'UserLegalHoldIllegalOperation,
                                                                            'LegalHoldCouldNotBlockConnections]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("legalhold"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (LockableFeaturePatch
                                                                                                LegalholdConfig)
                                                                                           :> Patch
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   LegalholdConfig)))))))))))))))
                                :<|> ((Named
                                         '("iget", SSOConfig)
                                         (Description ""
                                          :> (Summary "Get config for sso"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("sso"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  SSOConfig))))))))))
                                       :<|> (Named
                                               '("iput", SSOConfig)
                                               (Description ""
                                                :> (Summary "Put config for sso"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> (CanThrowMany '[]
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("sso"
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              (Feature
                                                                                                 SSOConfig)
                                                                                            :> Put
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    SSOConfig)))))))))))))
                                             :<|> Named
                                                    '("ipatch", SSOConfig)
                                                    (Description ""
                                                     :> (Summary "Patch config for sso"
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("sso"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (LockableFeaturePatch
                                                                                                      SSOConfig)
                                                                                                 :> Patch
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         SSOConfig)))))))))))))))
                                      :<|> ((Named
                                               '("iget", SearchVisibilityAvailableConfig)
                                               (Description ""
                                                :> (Summary "Get config for searchVisibility"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("searchVisibility"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SearchVisibilityAvailableConfig))))))))))
                                             :<|> (Named
                                                     '("iput", SearchVisibilityAvailableConfig)
                                                     (Description ""
                                                      :> (Summary "Put config for searchVisibility"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany '[]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("searchVisibility"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (Feature
                                                                                                       SearchVisibilityAvailableConfig)
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          SearchVisibilityAvailableConfig)))))))))))))
                                                   :<|> Named
                                                          '("ipatch",
                                                            SearchVisibilityAvailableConfig)
                                                          (Description ""
                                                           :> (Summary
                                                                 "Patch config for searchVisibility"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("searchVisibility"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (LockableFeaturePatch
                                                                                                            SearchVisibilityAvailableConfig)
                                                                                                       :> Patch
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               SearchVisibilityAvailableConfig)))))))))))))))
                                            :<|> ((Named
                                                     '("iget", SearchVisibilityInboundConfig)
                                                     (Description ""
                                                      :> (Summary
                                                            "Get config for searchVisibilityInbound"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("searchVisibilityInbound"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              SearchVisibilityInboundConfig))))))))))
                                                   :<|> (Named
                                                           '("iput", SearchVisibilityInboundConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Put config for searchVisibilityInbound"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("searchVisibilityInbound"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             SearchVisibilityInboundConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SearchVisibilityInboundConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch",
                                                                  SearchVisibilityInboundConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Patch config for searchVisibilityInbound"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("searchVisibilityInbound"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  SearchVisibilityInboundConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     SearchVisibilityInboundConfig)))))))))))))))
                                                  :<|> ((Named
                                                           '("iget", ValidateSAMLEmailsConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Get config for validateSAMLemails"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("validateSAMLemails"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    ValidateSAMLEmailsConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput", ValidateSAMLEmailsConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Put config for validateSAMLemails"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("validateSAMLemails"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   ValidateSAMLEmailsConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      ValidateSAMLEmailsConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch",
                                                                        ValidateSAMLEmailsConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for validateSAMLemails"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("validateSAMLemails"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        ValidateSAMLEmailsConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           ValidateSAMLEmailsConfig)))))))))))))))
                                                        :<|> ((Named
                                                                 '("iget", DigitalSignaturesConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Get config for digitalSignatures"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("digitalSignatures"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          DigitalSignaturesConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput",
                                                                         DigitalSignaturesConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for digitalSignatures"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("digitalSignatures"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         DigitalSignaturesConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            DigitalSignaturesConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch",
                                                                              DigitalSignaturesConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for digitalSignatures"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("digitalSignatures"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              DigitalSignaturesConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 DigitalSignaturesConfig)))))))))))))))
                                                              :<|> ((Named
                                                                       '("iget", AppLockConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for appLock"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("appLock"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                AppLockConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               AppLockConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for appLock"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("appLock"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               AppLockConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  AppLockConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    AppLockConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for appLock"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("appLock"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    AppLockConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       AppLockConfig)))))))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               FileSharingConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for fileSharing"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("fileSharing"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      FileSharingConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     FileSharingConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for fileSharing"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("fileSharing"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     FileSharingConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        FileSharingConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          FileSharingConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for fileSharing"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("fileSharing"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          FileSharingConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             FileSharingConfig)))))))))))))))
                                                                          :<|> (Named
                                                                                  '("iget",
                                                                                    ClassifiedDomainsConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Get config for classifiedDomains"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("classifiedDomains"
                                                                                                                   :> Get
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           ClassifiedDomainsConfig))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           ConferenceCallingConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for conferenceCalling"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("conferenceCalling"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  ConferenceCallingConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 ConferenceCallingConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for conferenceCalling"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("conferenceCalling"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 ConferenceCallingConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    ConferenceCallingConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      ConferenceCallingConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for conferenceCalling"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("conferenceCalling"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      ConferenceCallingConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         ConferenceCallingConfig)))))))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 SelfDeletingMessagesConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for selfDeletingMessages"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("selfDeletingMessages"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        SelfDeletingMessagesConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       SelfDeletingMessagesConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for selfDeletingMessages"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("selfDeletingMessages"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       SelfDeletingMessagesConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          SelfDeletingMessagesConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            SelfDeletingMessagesConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for selfDeletingMessages"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("selfDeletingMessages"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            SelfDeletingMessagesConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               SelfDeletingMessagesConfig)))))))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       GuestLinksConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for conversationGuestLinks"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("conversationGuestLinks"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              GuestLinksConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             GuestLinksConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for conversationGuestLinks"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("conversationGuestLinks"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             GuestLinksConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                GuestLinksConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  GuestLinksConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for conversationGuestLinks"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  GuestLinksConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     GuestLinksConfig)))))))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             SndFactorPasswordChallengeConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for sndFactorPasswordChallenge"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("sndFactorPasswordChallenge"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    SndFactorPasswordChallengeConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   SndFactorPasswordChallengeConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for sndFactorPasswordChallenge"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("sndFactorPasswordChallenge"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   SndFactorPasswordChallengeConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      SndFactorPasswordChallengeConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        SndFactorPasswordChallengeConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for sndFactorPasswordChallenge"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        SndFactorPasswordChallengeConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   MLSConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for mls"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("mls"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          MLSConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         MLSConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for mls"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("mls"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         MLSConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MLSConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              MLSConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for mls"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("mls"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              MLSConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 MLSConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               OutlookCalIntegrationConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for outlookCalIntegration"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("outlookCalIntegration"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      OutlookCalIntegrationConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     OutlookCalIntegrationConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for outlookCalIntegration"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("outlookCalIntegration"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     OutlookCalIntegrationConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        OutlookCalIntegrationConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          OutlookCalIntegrationConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for outlookCalIntegration"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("outlookCalIntegration"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          OutlookCalIntegrationConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             OutlookCalIntegrationConfig)))))))))))))))
                                                                                                                          :<|> ((Named
                                                                                                                                   '("iget",
                                                                                                                                     MlsE2EIdConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for mlsE2EId"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("mlsE2EId"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MlsE2EIdConfig))))))))))
                                                                                                                                 :<|> (Named
                                                                                                                                         '("iput",
                                                                                                                                           MlsE2EIdConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Put config for mlsE2EId"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("mlsE2EId"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Feature
                                                                                                                                                                                           MlsE2EIdConfig)
                                                                                                                                                                                      :> Put
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              MlsE2EIdConfig)))))))))))))
                                                                                                                                       :<|> Named
                                                                                                                                              '("ipatch",
                                                                                                                                                MlsE2EIdConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Patch config for mlsE2EId"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("mlsE2EId"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                MlsE2EIdConfig)
                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   MlsE2EIdConfig)))))))))))))))
                                                                                                                                :<|> ((Named
                                                                                                                                         '("iget",
                                                                                                                                           MlsMigrationConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for mlsMigration"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("mlsMigration"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  MlsMigrationConfig))))))))))
                                                                                                                                       :<|> (Named
                                                                                                                                               '("iput",
                                                                                                                                                 MlsMigrationConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Put config for mlsMigration"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                          '[]
                                                                                                                                                                        :> ("teams"
                                                                                                                                                                            :> (Capture
                                                                                                                                                                                  "tid"
                                                                                                                                                                                  TeamId
                                                                                                                                                                                :> ("features"
                                                                                                                                                                                    :> ("mlsMigration"
                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (Feature
                                                                                                                                                                                                 MlsMigrationConfig)
                                                                                                                                                                                            :> Put
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    MlsMigrationConfig)))))))))))))
                                                                                                                                             :<|> Named
                                                                                                                                                    '("ipatch",
                                                                                                                                                      MlsMigrationConfig)
                                                                                                                                                    (Description
                                                                                                                                                       ""
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Patch config for mlsMigration"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("mlsMigration"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                                                      MlsMigrationConfig)
                                                                                                                                                                                                 :> Patch
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         MlsMigrationConfig)))))))))))))))
                                                                                                                                      :<|> ((Named
                                                                                                                                               '("iget",
                                                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                                                               (Description
                                                                                                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                :> (Summary
                                                                                                                                                      "Get config for enforceFileDownloadLocation"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                             :<|> (Named
                                                                                                                                                     '("iput",
                                                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                                                     (Description
                                                                                                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Put config for enforceFileDownloadLocation"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                          :> (CanThrowMany
                                                                                                                                                                                '[]
                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                        "tid"
                                                                                                                                                                                        TeamId
                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (Feature
                                                                                                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                  :> Put
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                                   :<|> Named
                                                                                                                                                          '("ipatch",
                                                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                                                          (Description
                                                                                                                                                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Patch config for enforceFileDownloadLocation"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('MissingPermission
                                                                                                                                                                        'Nothing)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 TeamFeatureError
                                                                                                                                                                               :> (CanThrowMany
                                                                                                                                                                                     '[]
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                       :> Patch
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                            :<|> (Named
                                                                                                                                                    '("iget",
                                                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                                                    (Description
                                                                                                                                                       ""
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Get config for limitedEventFanout"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("teams"
                                                                                                                                                                         :> (Capture
                                                                                                                                                                               "tid"
                                                                                                                                                                               TeamId
                                                                                                                                                                             :> ("features"
                                                                                                                                                                                 :> ("limitedEventFanout"
                                                                                                                                                                                     :> Get
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             LimitedEventFanoutConfig))))))))))
                                                                                                                                                  :<|> (Named
                                                                                                                                                          '("iput",
                                                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                                                          (Description
                                                                                                                                                             ""
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Put config for limitedEventFanout"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('MissingPermission
                                                                                                                                                                        'Nothing)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 TeamFeatureError
                                                                                                                                                                               :> (CanThrowMany
                                                                                                                                                                                     '[]
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> ("limitedEventFanout"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (Feature
                                                                                                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                                                                                                       :> Put
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               LimitedEventFanoutConfig)))))))))))))
                                                                                                                                                        :<|> Named
                                                                                                                                                               '("ipatch",
                                                                                                                                                                 LimitedEventFanoutConfig)
                                                                                                                                                               (Description
                                                                                                                                                                  ""
                                                                                                                                                                :> (Summary
                                                                                                                                                                      "Patch config for limitedEventFanout"
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          ('MissingPermission
                                                                                                                                                                             'Nothing)
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                                          '[]
                                                                                                                                                                                        :> ("teams"
                                                                                                                                                                                            :> (Capture
                                                                                                                                                                                                  "tid"
                                                                                                                                                                                                  TeamId
                                                                                                                                                                                                :> ("features"
                                                                                                                                                                                                    :> ("limitedEventFanout"
                                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              (LockableFeaturePatch
                                                                                                                                                                                                                 LimitedEventFanoutConfig)
                                                                                                                                                                                                            :> Patch
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                                    LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                               :<|> (Named
                                       '("ilock", FileSharingConfig)
                                       (Summary "(Un-)lock fileSharing"
                                        :> (Description ""
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("fileSharing"
                                                                    :> (Capture
                                                                          "lockStatus" LockStatus
                                                                        :> Put
                                                                             '[JSON]
                                                                             LockStatusResponse)))))))))
                                     :<|> (Named
                                             '("ilock", ConferenceCallingConfig)
                                             (Summary "(Un-)lock conferenceCalling"
                                              :> (Description ""
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("conferenceCalling"
                                                                          :> (Capture
                                                                                "lockStatus"
                                                                                LockStatus
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   LockStatusResponse)))))))))
                                           :<|> (Named
                                                   '("ilock", SelfDeletingMessagesConfig)
                                                   (Summary "(Un-)lock selfDeletingMessages"
                                                    :> (Description ""
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("selfDeletingMessages"
                                                                                :> (Capture
                                                                                      "lockStatus"
                                                                                      LockStatus
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         LockStatusResponse)))))))))
                                                 :<|> (Named
                                                         '("ilock", GuestLinksConfig)
                                                         (Summary "(Un-)lock conversationGuestLinks"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("conversationGuestLinks"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock",
                                                                 SndFactorPasswordChallengeConfig)
                                                               (Summary
                                                                  "(Un-)lock sndFactorPasswordChallenge"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("sndFactorPasswordChallenge"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock", MLSConfig)
                                                                     (Summary "(Un-)lock mls"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mls"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock",
                                                                             OutlookCalIntegrationConfig)
                                                                           (Summary
                                                                              "(Un-)lock outlookCalIntegration"
                                                                            :> (Description ""
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("outlookCalIntegration"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("ilock",
                                                                                   MlsE2EIdConfig)
                                                                                 (Summary
                                                                                    "(Un-)lock mlsE2EId"
                                                                                  :> (Description ""
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mlsE2EId"
                                                                                                              :> (Capture
                                                                                                                    "lockStatus"
                                                                                                                    LockStatus
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       LockStatusResponse)))))))))
                                                                               :<|> (Named
                                                                                       '("ilock",
                                                                                         MlsMigrationConfig)
                                                                                       (Summary
                                                                                          "(Un-)lock mlsMigration"
                                                                                        :> (Description
                                                                                              ""
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mlsMigration"
                                                                                                                    :> (Capture
                                                                                                                          "lockStatus"
                                                                                                                          LockStatus
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             LockStatusResponse)))))))))
                                                                                     :<|> (Named
                                                                                             '("ilock",
                                                                                               EnforceFileDownloadLocationConfig)
                                                                                             (Summary
                                                                                                "(Un-)lock enforceFileDownloadLocation"
                                                                                              :> (Description
                                                                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("enforceFileDownloadLocation"
                                                                                                                          :> (Capture
                                                                                                                                "lockStatus"
                                                                                                                                LockStatus
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   LockStatusResponse)))))))))
                                                                                           :<|> (Named
                                                                                                   '("igetmulti",
                                                                                                     SearchVisibilityInboundConfig)
                                                                                                   (Summary
                                                                                                      "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                                    :> ("features-multi-teams"
                                                                                                        :> ("searchVisibilityInbound"
                                                                                                            :> (ReqBody
                                                                                                                  '[JSON]
                                                                                                                  TeamFeatureNoConfigMultiRequest
                                                                                                                :> Post
                                                                                                                     '[JSON]
                                                                                                                     (TeamFeatureNoConfigMultiResponse
                                                                                                                        SearchVisibilityInboundConfig)))))
                                                                                                 :<|> Named
                                                                                                        "feature-configs-internal"
                                                                                                        (Summary
                                                                                                           "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                                         :> ("feature-configs"
                                                                                                             :> (CanThrow
                                                                                                                   ('MissingPermission
                                                                                                                      'Nothing)
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (QueryParam'
                                                                                                                               '[Optional,
                                                                                                                                 Strict,
                                                                                                                                 Description
                                                                                                                                   "Optional user id"]
                                                                                                                               "user_id"
                                                                                                                               UserId
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  AllTeamFeatures))))))))))))))))))
                              :<|> (IFederationAPI :<|> (IConversationAPI :<|> IEJPDAPI)))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "guard-legalhold-policy-conflicts"
        ("guard-legalhold-policy-conflicts"
         :> (CanThrow 'MissingLegalholdConsent
             :> (CanThrow 'MissingLegalholdConsentOldClients
                 :> (ReqBody '[JSON] GuardLegalholdPolicyConflicts
                     :> MultiVerb
                          'PUT '[JSON] '[RespondEmpty 200 "Guard Legalhold Policy"] ()))))
      :<|> (("legalhold"
             :> ("whitelisted-teams"
                 :> (Capture "tid" TeamId
                     :> (Named
                           "set-team-legalhold-whitelisted"
                           (MultiVerb
                              'PUT '[JSON] '[RespondEmpty 200 "Team Legalhold Whitelisted"] ())
                         :<|> (Named
                                 "unset-team-legalhold-whitelisted"
                                 (MultiVerb
                                    'DELETE
                                    '[JSON]
                                    '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
                                    ())
                               :<|> Named
                                      "get-team-legalhold-whitelisted"
                                      (MultiVerb
                                         'GET
                                         '[JSON]
                                         '[RespondEmpty 404 "Team not Legalhold Whitelisted",
                                           RespondEmpty 200 "Team Legalhold Whitelisted"]
                                         Bool))))))
            :<|> (("teams"
                   :> (Capture "tid" TeamId
                       :> (Named
                             "get-team-internal"
                             (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
                           :<|> (Named
                                   "create-binding-team"
                                   (ZUser
                                    :> (ReqBody '[JSON] BindingNewTeam
                                        :> MultiVerb
                                             'PUT
                                             '[JSON]
                                             '[WithHeaders
                                                 '[Header "Location" TeamId]
                                                 TeamId
                                                 (RespondEmpty 201 "OK")]
                                             TeamId))
                                 :<|> (Named
                                         "delete-binding-team"
                                         (CanThrow 'NoBindingTeam
                                          :> (CanThrow 'NotAOneMemberTeam
                                              :> (CanThrow 'DeleteQueueFull
                                                  :> (CanThrow 'TeamNotFound
                                                      :> (QueryFlag "force"
                                                          :> MultiVerb
                                                               'DELETE
                                                               '[JSON]
                                                               '[RespondEmpty 202 "OK"]
                                                               ())))))
                                       :<|> (Named
                                               "get-team-name"
                                               ("name"
                                                :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
                                             :<|> (Named
                                                     "update-team-status"
                                                     ("status"
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow 'InvalidTeamStatusUpdate
                                                              :> (ReqBody '[JSON] TeamStatusUpdate
                                                                  :> MultiVerb
                                                                       'PUT
                                                                       '[JSON]
                                                                       '[RespondEmpty 200 "OK"]
                                                                       ()))))
                                                   :<|> (("members"
                                                          :> (Named
                                                                "unchecked-add-team-member"
                                                                (CanThrow 'TooManyTeamMembers
                                                                 :> (CanThrow
                                                                       'TooManyTeamMembersOnTeamWithLegalhold
                                                                     :> (CanThrow 'TooManyTeamAdmins
                                                                         :> (ReqBody
                                                                               '[JSON] NewTeamMember
                                                                             :> MultiVerb
                                                                                  'POST
                                                                                  '[JSON]
                                                                                  '[RespondEmpty
                                                                                      200 "OK"]
                                                                                  ()))))
                                                              :<|> (Named
                                                                      "unchecked-get-team-members"
                                                                      (QueryParam'
                                                                         '[Strict]
                                                                         "maxResults"
                                                                         (Range
                                                                            1
                                                                            HardTruncationLimit
                                                                            Int32)
                                                                       :> Get
                                                                            '[JSON] TeamMemberList)
                                                                    :<|> (Named
                                                                            "unchecked-get-team-member"
                                                                            (Capture "uid" UserId
                                                                             :> (CanThrow
                                                                                   'TeamMemberNotFound
                                                                                 :> Get
                                                                                      '[JSON]
                                                                                      TeamMember))
                                                                          :<|> (Named
                                                                                  "can-user-join-team"
                                                                                  ("check"
                                                                                   :> (CanThrow
                                                                                         'TooManyTeamMembersOnTeamWithLegalhold
                                                                                       :> MultiVerb
                                                                                            'GET
                                                                                            '[JSON]
                                                                                            '[RespondEmpty
                                                                                                200
                                                                                                "User can join"]
                                                                                            ()))
                                                                                :<|> Named
                                                                                       "unchecked-update-team-member"
                                                                                       (CanThrow
                                                                                          'AccessDenied
                                                                                        :> (CanThrow
                                                                                              'InvalidPermissions
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> (CanThrow
                                                                                                      'TeamMemberNotFound
                                                                                                    :> (CanThrow
                                                                                                          'TooManyTeamAdmins
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  ('MissingPermission
                                                                                                                     'Nothing)
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      NewTeamMember
                                                                                                                    :> MultiVerb
                                                                                                                         'PUT
                                                                                                                         '[JSON]
                                                                                                                         '[RespondEmpty
                                                                                                                             200
                                                                                                                             ""]
                                                                                                                         ())))))))))))))
                                                         :<|> (Named
                                                                 "user-is-team-owner"
                                                                 ("is-team-owner"
                                                                  :> (Capture "uid" UserId
                                                                      :> (CanThrow 'AccessDenied
                                                                          :> (CanThrow
                                                                                'TeamMemberNotFound
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> MultiVerb
                                                                                       'GET
                                                                                       '[JSON]
                                                                                       '[RespondEmpty
                                                                                           200
                                                                                           "User is team owner"]
                                                                                       ())))))
                                                               :<|> ("search-visibility"
                                                                     :> (Named
                                                                           "get-search-visibility-internal"
                                                                           (Get
                                                                              '[JSON]
                                                                              TeamSearchVisibilityView)
                                                                         :<|> Named
                                                                                "set-search-visibility-internal"
                                                                                (CanThrow
                                                                                   'TeamSearchVisibilityNotEnabled
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   TeamSearchVisibilityView
                                                                                                 :> MultiVerb
                                                                                                      'PUT
                                                                                                      '[JSON]
                                                                                                      '[RespondEmpty
                                                                                                          204
                                                                                                          "OK"]
                                                                                                      ()))))))))))))))))
                  :<|> ((Named
                           "get-team-members"
                           (CanThrow 'NonBindingTeam
                            :> (CanThrow 'TeamNotFound
                                :> ("users"
                                    :> (Capture "uid" UserId
                                        :> ("team" :> ("members" :> Get '[JSON] TeamMemberList))))))
                         :<|> (Named
                                 "get-team-id"
                                 (CanThrow 'NonBindingTeam
                                  :> (CanThrow 'TeamNotFound
                                      :> ("users"
                                          :> (Capture "uid" UserId
                                              :> ("team" :> Get '[JSON] TeamId)))))
                               :<|> (Named
                                       "test-get-clients"
                                       ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
                                     :<|> (Named
                                             "test-add-client"
                                             ("clients"
                                              :> (ZUser
                                                  :> (Capture "cid" ClientId
                                                      :> MultiVerb
                                                           'POST
                                                           '[JSON]
                                                           '[RespondEmpty 200 "OK"]
                                                           ())))
                                           :<|> (Named
                                                   "test-delete-client"
                                                   ("clients"
                                                    :> (ZUser
                                                        :> (Capture "cid" ClientId
                                                            :> MultiVerb
                                                                 'DELETE
                                                                 '[JSON]
                                                                 '[RespondEmpty 200 "OK"]
                                                                 ())))
                                                 :<|> (Named
                                                         "add-service"
                                                         ("services"
                                                          :> (ReqBody '[JSON] Service
                                                              :> MultiVerb
                                                                   'POST
                                                                   '[JSON]
                                                                   '[RespondEmpty 200 "OK"]
                                                                   ()))
                                                       :<|> (Named
                                                               "delete-service"
                                                               ("services"
                                                                :> (ReqBody '[JSON] ServiceRef
                                                                    :> MultiVerb
                                                                         'DELETE
                                                                         '[JSON]
                                                                         '[RespondEmpty 200 "OK"]
                                                                         ()))
                                                             :<|> (Named
                                                                     "i-add-bot"
                                                                     (CanThrow
                                                                        ('ActionDenied
                                                                           'AddConversationMember)
                                                                      :> (CanThrow 'ConvNotFound
                                                                          :> (CanThrow
                                                                                'InvalidOperation
                                                                              :> (CanThrow
                                                                                    'TooManyMembers
                                                                                  :> ("bots"
                                                                                      :> (ZLocalUser
                                                                                          :> (ZConn
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    AddBot
                                                                                                  :> Post
                                                                                                       '[JSON]
                                                                                                       Event))))))))
                                                                   :<|> (Named
                                                                           "delete-bot"
                                                                           (CanThrow 'ConvNotFound
                                                                            :> (CanThrow
                                                                                  ('ActionDenied
                                                                                     'RemoveConversationMember)
                                                                                :> ("bots"
                                                                                    :> (ZLocalUser
                                                                                        :> (ZOptConn
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  RemoveBot
                                                                                                :> MultiVerb
                                                                                                     'DELETE
                                                                                                     '[JSON]
                                                                                                     (UpdateResponses
                                                                                                        "Bot not found"
                                                                                                        "Bot deleted"
                                                                                                        Event)
                                                                                                     (UpdateResult
                                                                                                        Event)))))))
                                                                         :<|> (Named
                                                                                 "put-custom-backend"
                                                                                 ("custom-backend"
                                                                                  :> ("by-domain"
                                                                                      :> (Capture
                                                                                            "domain"
                                                                                            Domain
                                                                                          :> (ReqBody
                                                                                                '[JSON]
                                                                                                CustomBackend
                                                                                              :> MultiVerb
                                                                                                   'PUT
                                                                                                   '[JSON]
                                                                                                   '[RespondEmpty
                                                                                                       201
                                                                                                       "OK"]
                                                                                                   ()))))
                                                                               :<|> Named
                                                                                      "delete-custom-backend"
                                                                                      ("custom-backend"
                                                                                       :> ("by-domain"
                                                                                           :> (Capture
                                                                                                 "domain"
                                                                                                 Domain
                                                                                               :> MultiVerb
                                                                                                    'DELETE
                                                                                                    '[JSON]
                                                                                                    '[RespondEmpty
                                                                                                        200
                                                                                                        "OK"]
                                                                                                    ())))))))))))))
                        :<|> (Named
                                "upsert-one2one"
                                (Summary "Create or Update a connect or one2one conversation."
                                 :> ("conversations"
                                     :> ("one2one"
                                         :> ("upsert"
                                             :> (ReqBody '[JSON] UpsertOne2OneConversationRequest
                                                 :> MultiVerb
                                                      'POST
                                                      '[JSON]
                                                      '[RespondEmpty 200 "Upsert One2One Policy"]
                                                      ())))))
                              :<|> ((((Named
                                         '("iget", LegalholdConfig)
                                         (Description ""
                                          :> (Summary "Get config for legalhold"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("legalhold"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  LegalholdConfig))))))))))
                                       :<|> (Named
                                               '("iput", LegalholdConfig)
                                               (Description ""
                                                :> (Summary "Put config for legalhold"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> (CanThrowMany
                                                                          '[ 'ActionDenied
                                                                               'RemoveConversationMember,
                                                                             'CannotEnableLegalHoldServiceLargeTeam,
                                                                             'LegalHoldNotEnabled,
                                                                             'LegalHoldDisableUnimplemented,
                                                                             'LegalHoldServiceNotRegistered,
                                                                             'UserLegalHoldIllegalOperation,
                                                                             'LegalHoldCouldNotBlockConnections]
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("legalhold"
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              (Feature
                                                                                                 LegalholdConfig)
                                                                                            :> Put
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    LegalholdConfig)))))))))))))
                                             :<|> Named
                                                    '("ipatch", LegalholdConfig)
                                                    (Description ""
                                                     :> (Summary "Patch config for legalhold"
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany
                                                                               '[ 'ActionDenied
                                                                                    'RemoveConversationMember,
                                                                                  'CannotEnableLegalHoldServiceLargeTeam,
                                                                                  'LegalHoldNotEnabled,
                                                                                  'LegalHoldDisableUnimplemented,
                                                                                  'LegalHoldServiceNotRegistered,
                                                                                  'UserLegalHoldIllegalOperation,
                                                                                  'LegalHoldCouldNotBlockConnections]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("legalhold"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (LockableFeaturePatch
                                                                                                      LegalholdConfig)
                                                                                                 :> Patch
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         LegalholdConfig)))))))))))))))
                                      :<|> ((Named
                                               '("iget", SSOConfig)
                                               (Description ""
                                                :> (Summary "Get config for sso"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("sso"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SSOConfig))))))))))
                                             :<|> (Named
                                                     '("iput", SSOConfig)
                                                     (Description ""
                                                      :> (Summary "Put config for sso"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany '[]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("sso"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (Feature
                                                                                                       SSOConfig)
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          SSOConfig)))))))))))))
                                                   :<|> Named
                                                          '("ipatch", SSOConfig)
                                                          (Description ""
                                                           :> (Summary "Patch config for sso"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("sso"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (LockableFeaturePatch
                                                                                                            SSOConfig)
                                                                                                       :> Patch
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               SSOConfig)))))))))))))))
                                            :<|> ((Named
                                                     '("iget", SearchVisibilityAvailableConfig)
                                                     (Description ""
                                                      :> (Summary "Get config for searchVisibility"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("searchVisibility"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              SearchVisibilityAvailableConfig))))))))))
                                                   :<|> (Named
                                                           '("iput",
                                                             SearchVisibilityAvailableConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Put config for searchVisibility"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("searchVisibility"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             SearchVisibilityAvailableConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SearchVisibilityAvailableConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch",
                                                                  SearchVisibilityAvailableConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Patch config for searchVisibility"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("searchVisibility"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  SearchVisibilityAvailableConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     SearchVisibilityAvailableConfig)))))))))))))))
                                                  :<|> ((Named
                                                           '("iget", SearchVisibilityInboundConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Get config for searchVisibilityInbound"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("searchVisibilityInbound"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    SearchVisibilityInboundConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput",
                                                                   SearchVisibilityInboundConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Put config for searchVisibilityInbound"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("searchVisibilityInbound"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   SearchVisibilityInboundConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      SearchVisibilityInboundConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch",
                                                                        SearchVisibilityInboundConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for searchVisibilityInbound"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("searchVisibilityInbound"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        SearchVisibilityInboundConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           SearchVisibilityInboundConfig)))))))))))))))
                                                        :<|> ((Named
                                                                 '("iget", ValidateSAMLEmailsConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Get config for validateSAMLemails"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("validateSAMLemails"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          ValidateSAMLEmailsConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput",
                                                                         ValidateSAMLEmailsConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for validateSAMLemails"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("validateSAMLemails"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         ValidateSAMLEmailsConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            ValidateSAMLEmailsConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch",
                                                                              ValidateSAMLEmailsConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for validateSAMLemails"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("validateSAMLemails"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              ValidateSAMLEmailsConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 ValidateSAMLEmailsConfig)))))))))))))))
                                                              :<|> ((Named
                                                                       '("iget",
                                                                         DigitalSignaturesConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for digitalSignatures"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("digitalSignatures"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                DigitalSignaturesConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               DigitalSignaturesConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for digitalSignatures"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("digitalSignatures"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               DigitalSignaturesConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  DigitalSignaturesConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    DigitalSignaturesConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for digitalSignatures"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("digitalSignatures"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    DigitalSignaturesConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       DigitalSignaturesConfig)))))))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               AppLockConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for appLock"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("appLock"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      AppLockConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     AppLockConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for appLock"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("appLock"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     AppLockConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        AppLockConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          AppLockConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for appLock"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("appLock"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          AppLockConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             AppLockConfig)))))))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     FileSharingConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for fileSharing"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("fileSharing"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            FileSharingConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           FileSharingConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for fileSharing"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("fileSharing"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           FileSharingConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              FileSharingConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                FileSharingConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for fileSharing"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("fileSharing"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                FileSharingConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   FileSharingConfig)))))))))))))))
                                                                                :<|> (Named
                                                                                        '("iget",
                                                                                          ClassifiedDomainsConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Get config for classifiedDomains"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("classifiedDomains"
                                                                                                                         :> Get
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 ClassifiedDomainsConfig))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 ConferenceCallingConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for conferenceCalling"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("conferenceCalling"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        ConferenceCallingConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       ConferenceCallingConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for conferenceCalling"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("conferenceCalling"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       ConferenceCallingConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          ConferenceCallingConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            ConferenceCallingConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for conferenceCalling"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("conferenceCalling"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            ConferenceCallingConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               ConferenceCallingConfig)))))))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       SelfDeletingMessagesConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for selfDeletingMessages"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("selfDeletingMessages"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              SelfDeletingMessagesConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             SelfDeletingMessagesConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for selfDeletingMessages"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("selfDeletingMessages"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             SelfDeletingMessagesConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                SelfDeletingMessagesConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  SelfDeletingMessagesConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for selfDeletingMessages"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("selfDeletingMessages"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  SelfDeletingMessagesConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     SelfDeletingMessagesConfig)))))))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             GuestLinksConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for conversationGuestLinks"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("conversationGuestLinks"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    GuestLinksConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   GuestLinksConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for conversationGuestLinks"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("conversationGuestLinks"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   GuestLinksConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      GuestLinksConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        GuestLinksConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for conversationGuestLinks"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        GuestLinksConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           GuestLinksConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   SndFactorPasswordChallengeConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for sndFactorPasswordChallenge"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("sndFactorPasswordChallenge"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          SndFactorPasswordChallengeConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         SndFactorPasswordChallengeConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for sndFactorPasswordChallenge"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("sndFactorPasswordChallenge"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         SndFactorPasswordChallengeConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            SndFactorPasswordChallengeConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              SndFactorPasswordChallengeConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for sndFactorPasswordChallenge"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("sndFactorPasswordChallenge"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              SndFactorPasswordChallengeConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         MLSConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for mls"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("mls"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                MLSConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               MLSConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for mls"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("mls"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               MLSConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  MLSConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    MLSConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for mls"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("mls"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    MLSConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       MLSConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                                          :<|> ((Named
                                                                                                                                   '("iget",
                                                                                                                                     OutlookCalIntegrationConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for outlookCalIntegration"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("outlookCalIntegration"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            OutlookCalIntegrationConfig))))))))))
                                                                                                                                 :<|> (Named
                                                                                                                                         '("iput",
                                                                                                                                           OutlookCalIntegrationConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Put config for outlookCalIntegration"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("outlookCalIntegration"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Feature
                                                                                                                                                                                           OutlookCalIntegrationConfig)
                                                                                                                                                                                      :> Put
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              OutlookCalIntegrationConfig)))))))))))))
                                                                                                                                       :<|> Named
                                                                                                                                              '("ipatch",
                                                                                                                                                OutlookCalIntegrationConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Patch config for outlookCalIntegration"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("outlookCalIntegration"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                OutlookCalIntegrationConfig)
                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   OutlookCalIntegrationConfig)))))))))))))))
                                                                                                                                :<|> ((Named
                                                                                                                                         '("iget",
                                                                                                                                           MlsE2EIdConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for mlsE2EId"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("mlsE2EId"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  MlsE2EIdConfig))))))))))
                                                                                                                                       :<|> (Named
                                                                                                                                               '("iput",
                                                                                                                                                 MlsE2EIdConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Put config for mlsE2EId"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                          '[]
                                                                                                                                                                        :> ("teams"
                                                                                                                                                                            :> (Capture
                                                                                                                                                                                  "tid"
                                                                                                                                                                                  TeamId
                                                                                                                                                                                :> ("features"
                                                                                                                                                                                    :> ("mlsE2EId"
                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (Feature
                                                                                                                                                                                                 MlsE2EIdConfig)
                                                                                                                                                                                            :> Put
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    MlsE2EIdConfig)))))))))))))
                                                                                                                                             :<|> Named
                                                                                                                                                    '("ipatch",
                                                                                                                                                      MlsE2EIdConfig)
                                                                                                                                                    (Description
                                                                                                                                                       ""
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Patch config for mlsE2EId"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("mlsE2EId"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                                                      MlsE2EIdConfig)
                                                                                                                                                                                                 :> Patch
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         MlsE2EIdConfig)))))))))))))))
                                                                                                                                      :<|> ((Named
                                                                                                                                               '("iget",
                                                                                                                                                 MlsMigrationConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Get config for mlsMigration"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("mlsMigration"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        MlsMigrationConfig))))))))))
                                                                                                                                             :<|> (Named
                                                                                                                                                     '("iput",
                                                                                                                                                       MlsMigrationConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Put config for mlsMigration"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                          :> (CanThrowMany
                                                                                                                                                                                '[]
                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                        "tid"
                                                                                                                                                                                        TeamId
                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                          :> ("mlsMigration"
                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (Feature
                                                                                                                                                                                                       MlsMigrationConfig)
                                                                                                                                                                                                  :> Put
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          MlsMigrationConfig)))))))))))))
                                                                                                                                                   :<|> Named
                                                                                                                                                          '("ipatch",
                                                                                                                                                            MlsMigrationConfig)
                                                                                                                                                          (Description
                                                                                                                                                             ""
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Patch config for mlsMigration"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('MissingPermission
                                                                                                                                                                        'Nothing)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 TeamFeatureError
                                                                                                                                                                               :> (CanThrowMany
                                                                                                                                                                                     '[]
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> ("mlsMigration"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                                                                            MlsMigrationConfig)
                                                                                                                                                                                                       :> Patch
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               MlsMigrationConfig)))))))))))))))
                                                                                                                                            :<|> ((Named
                                                                                                                                                     '("iget",
                                                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                                                     (Description
                                                                                                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Get config for enforceFileDownloadLocation"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                                                                      :> Get
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                                   :<|> (Named
                                                                                                                                                           '("iput",
                                                                                                                                                             EnforceFileDownloadLocationConfig)
                                                                                                                                                           (Description
                                                                                                                                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Put config for enforceFileDownloadLocation"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      ('MissingPermission
                                                                                                                                                                         'Nothing)
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  TeamFeatureError
                                                                                                                                                                                :> (CanThrowMany
                                                                                                                                                                                      '[]
                                                                                                                                                                                    :> ("teams"
                                                                                                                                                                                        :> (Capture
                                                                                                                                                                                              "tid"
                                                                                                                                                                                              TeamId
                                                                                                                                                                                            :> ("features"
                                                                                                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (Feature
                                                                                                                                                                                                             EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                        :> Put
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                                         :<|> Named
                                                                                                                                                                '("ipatch",
                                                                                                                                                                  EnforceFileDownloadLocationConfig)
                                                                                                                                                                (Description
                                                                                                                                                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                 :> (Summary
                                                                                                                                                                       "Patch config for enforceFileDownloadLocation"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('MissingPermission
                                                                                                                                                                              'Nothing)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       TeamFeatureError
                                                                                                                                                                                     :> (CanThrowMany
                                                                                                                                                                                           '[]
                                                                                                                                                                                         :> ("teams"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "tid"
                                                                                                                                                                                                   TeamId
                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                     :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                                                                  EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                             :> Patch
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                                  :<|> (Named
                                                                                                                                                          '("iget",
                                                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                                                          (Description
                                                                                                                                                             ""
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Get config for limitedEventFanout"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('MissingPermission
                                                                                                                                                                        'Nothing)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("teams"
                                                                                                                                                                               :> (Capture
                                                                                                                                                                                     "tid"
                                                                                                                                                                                     TeamId
                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                       :> ("limitedEventFanout"
                                                                                                                                                                                           :> Get
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   LimitedEventFanoutConfig))))))))))
                                                                                                                                                        :<|> (Named
                                                                                                                                                                '("iput",
                                                                                                                                                                  LimitedEventFanoutConfig)
                                                                                                                                                                (Description
                                                                                                                                                                   ""
                                                                                                                                                                 :> (Summary
                                                                                                                                                                       "Put config for limitedEventFanout"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('MissingPermission
                                                                                                                                                                              'Nothing)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       TeamFeatureError
                                                                                                                                                                                     :> (CanThrowMany
                                                                                                                                                                                           '[]
                                                                                                                                                                                         :> ("teams"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "tid"
                                                                                                                                                                                                   TeamId
                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                     :> ("limitedEventFanout"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               (Feature
                                                                                                                                                                                                                  LimitedEventFanoutConfig)
                                                                                                                                                                                                             :> Put
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     LimitedEventFanoutConfig)))))))))))))
                                                                                                                                                              :<|> Named
                                                                                                                                                                     '("ipatch",
                                                                                                                                                                       LimitedEventFanoutConfig)
                                                                                                                                                                     (Description
                                                                                                                                                                        ""
                                                                                                                                                                      :> (Summary
                                                                                                                                                                            "Patch config for limitedEventFanout"
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                ('MissingPermission
                                                                                                                                                                                   'Nothing)
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                                          :> (CanThrowMany
                                                                                                                                                                                                '[]
                                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                                        "tid"
                                                                                                                                                                                                        TeamId
                                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                                          :> ("limitedEventFanout"
                                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    (LockableFeaturePatch
                                                                                                                                                                                                                       LimitedEventFanoutConfig)
                                                                                                                                                                                                                  :> Patch
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                                          LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                                     :<|> (Named
                                             '("ilock", FileSharingConfig)
                                             (Summary "(Un-)lock fileSharing"
                                              :> (Description ""
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("fileSharing"
                                                                          :> (Capture
                                                                                "lockStatus"
                                                                                LockStatus
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   LockStatusResponse)))))))))
                                           :<|> (Named
                                                   '("ilock", ConferenceCallingConfig)
                                                   (Summary "(Un-)lock conferenceCalling"
                                                    :> (Description ""
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("conferenceCalling"
                                                                                :> (Capture
                                                                                      "lockStatus"
                                                                                      LockStatus
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         LockStatusResponse)))))))))
                                                 :<|> (Named
                                                         '("ilock", SelfDeletingMessagesConfig)
                                                         (Summary "(Un-)lock selfDeletingMessages"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("selfDeletingMessages"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock", GuestLinksConfig)
                                                               (Summary
                                                                  "(Un-)lock conversationGuestLinks"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("conversationGuestLinks"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock",
                                                                       SndFactorPasswordChallengeConfig)
                                                                     (Summary
                                                                        "(Un-)lock sndFactorPasswordChallenge"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("sndFactorPasswordChallenge"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock", MLSConfig)
                                                                           (Summary "(Un-)lock mls"
                                                                            :> (Description ""
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mls"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("ilock",
                                                                                   OutlookCalIntegrationConfig)
                                                                                 (Summary
                                                                                    "(Un-)lock outlookCalIntegration"
                                                                                  :> (Description ""
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("outlookCalIntegration"
                                                                                                              :> (Capture
                                                                                                                    "lockStatus"
                                                                                                                    LockStatus
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       LockStatusResponse)))))))))
                                                                               :<|> (Named
                                                                                       '("ilock",
                                                                                         MlsE2EIdConfig)
                                                                                       (Summary
                                                                                          "(Un-)lock mlsE2EId"
                                                                                        :> (Description
                                                                                              ""
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mlsE2EId"
                                                                                                                    :> (Capture
                                                                                                                          "lockStatus"
                                                                                                                          LockStatus
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             LockStatusResponse)))))))))
                                                                                     :<|> (Named
                                                                                             '("ilock",
                                                                                               MlsMigrationConfig)
                                                                                             (Summary
                                                                                                "(Un-)lock mlsMigration"
                                                                                              :> (Description
                                                                                                    ""
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mlsMigration"
                                                                                                                          :> (Capture
                                                                                                                                "lockStatus"
                                                                                                                                LockStatus
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   LockStatusResponse)))))))))
                                                                                           :<|> (Named
                                                                                                   '("ilock",
                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                   (Summary
                                                                                                      "(Un-)lock enforceFileDownloadLocation"
                                                                                                    :> (Description
                                                                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                                                :> (Capture
                                                                                                                                      "lockStatus"
                                                                                                                                      LockStatus
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         LockStatusResponse)))))))))
                                                                                                 :<|> (Named
                                                                                                         '("igetmulti",
                                                                                                           SearchVisibilityInboundConfig)
                                                                                                         (Summary
                                                                                                            "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                                          :> ("features-multi-teams"
                                                                                                              :> ("searchVisibilityInbound"
                                                                                                                  :> (ReqBody
                                                                                                                        '[JSON]
                                                                                                                        TeamFeatureNoConfigMultiRequest
                                                                                                                      :> Post
                                                                                                                           '[JSON]
                                                                                                                           (TeamFeatureNoConfigMultiResponse
                                                                                                                              SearchVisibilityInboundConfig)))))
                                                                                                       :<|> Named
                                                                                                              "feature-configs-internal"
                                                                                                              (Summary
                                                                                                                 "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                                               :> ("feature-configs"
                                                                                                                   :> (CanThrow
                                                                                                                         ('MissingPermission
                                                                                                                            'Nothing)
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> (QueryParam'
                                                                                                                                     '[Optional,
                                                                                                                                       Strict,
                                                                                                                                       Description
                                                                                                                                         "Optional user id"]
                                                                                                                                     "user_id"
                                                                                                                                     UserId
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        AllTeamFeatures))))))))))))))))))
                                    :<|> (IFederationAPI
                                          :<|> (IConversationAPI :<|> IEJPDAPI))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  ("legalhold"
   :> ("whitelisted-teams"
       :> (Capture "tid" TeamId
           :> (Named
                 "set-team-legalhold-whitelisted"
                 (MultiVerb
                    'PUT '[JSON] '[RespondEmpty 200 "Team Legalhold Whitelisted"] ())
               :<|> (Named
                       "unset-team-legalhold-whitelisted"
                       (MultiVerb
                          'DELETE
                          '[JSON]
                          '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
                          ())
                     :<|> Named
                            "get-team-legalhold-whitelisted"
                            (MultiVerb
                               'GET
                               '[JSON]
                               '[RespondEmpty 404 "Team not Legalhold Whitelisted",
                                 RespondEmpty 200 "Team Legalhold Whitelisted"]
                               Bool))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 ILegalholdWhitelistedTeamsAPI GalleyEffects
legalholdWhitelistedTeamsAPI
      API
  ("legalhold"
   :> ("whitelisted-teams"
       :> (Capture "tid" TeamId
           :> (Named
                 "set-team-legalhold-whitelisted"
                 (MultiVerb
                    'PUT '[JSON] '[RespondEmpty 200 "Team Legalhold Whitelisted"] ())
               :<|> (Named
                       "unset-team-legalhold-whitelisted"
                       (MultiVerb
                          'DELETE
                          '[JSON]
                          '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
                          ())
                     :<|> Named
                            "get-team-legalhold-whitelisted"
                            (MultiVerb
                               'GET
                               '[JSON]
                               '[RespondEmpty 404 "Team not Legalhold Whitelisted",
                                 RespondEmpty 200 "Team Legalhold Whitelisted"]
                               Bool))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     (("teams"
       :> (Capture "tid" TeamId
           :> (Named
                 "get-team-internal"
                 (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
               :<|> (Named
                       "create-binding-team"
                       (ZUser
                        :> (ReqBody '[JSON] BindingNewTeam
                            :> MultiVerb
                                 'PUT
                                 '[JSON]
                                 '[WithHeaders
                                     '[Header "Location" TeamId] TeamId (RespondEmpty 201 "OK")]
                                 TeamId))
                     :<|> (Named
                             "delete-binding-team"
                             (CanThrow 'NoBindingTeam
                              :> (CanThrow 'NotAOneMemberTeam
                                  :> (CanThrow 'DeleteQueueFull
                                      :> (CanThrow 'TeamNotFound
                                          :> (QueryFlag "force"
                                              :> MultiVerb
                                                   'DELETE '[JSON] '[RespondEmpty 202 "OK"] ())))))
                           :<|> (Named
                                   "get-team-name"
                                   ("name" :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
                                 :<|> (Named
                                         "update-team-status"
                                         ("status"
                                          :> (CanThrow 'TeamNotFound
                                              :> (CanThrow 'InvalidTeamStatusUpdate
                                                  :> (ReqBody '[JSON] TeamStatusUpdate
                                                      :> MultiVerb
                                                           'PUT
                                                           '[JSON]
                                                           '[RespondEmpty 200 "OK"]
                                                           ()))))
                                       :<|> (("members"
                                              :> (Named
                                                    "unchecked-add-team-member"
                                                    (CanThrow 'TooManyTeamMembers
                                                     :> (CanThrow
                                                           'TooManyTeamMembersOnTeamWithLegalhold
                                                         :> (CanThrow 'TooManyTeamAdmins
                                                             :> (ReqBody '[JSON] NewTeamMember
                                                                 :> MultiVerb
                                                                      'POST
                                                                      '[JSON]
                                                                      '[RespondEmpty 200 "OK"]
                                                                      ()))))
                                                  :<|> (Named
                                                          "unchecked-get-team-members"
                                                          (QueryParam'
                                                             '[Strict]
                                                             "maxResults"
                                                             (Range 1 HardTruncationLimit Int32)
                                                           :> Get '[JSON] TeamMemberList)
                                                        :<|> (Named
                                                                "unchecked-get-team-member"
                                                                (Capture "uid" UserId
                                                                 :> (CanThrow 'TeamMemberNotFound
                                                                     :> Get '[JSON] TeamMember))
                                                              :<|> (Named
                                                                      "can-user-join-team"
                                                                      ("check"
                                                                       :> (CanThrow
                                                                             'TooManyTeamMembersOnTeamWithLegalhold
                                                                           :> MultiVerb
                                                                                'GET
                                                                                '[JSON]
                                                                                '[RespondEmpty
                                                                                    200
                                                                                    "User can join"]
                                                                                ()))
                                                                    :<|> Named
                                                                           "unchecked-update-team-member"
                                                                           (CanThrow 'AccessDenied
                                                                            :> (CanThrow
                                                                                  'InvalidPermissions
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> (CanThrow
                                                                                          'TeamMemberNotFound
                                                                                        :> (CanThrow
                                                                                              'TooManyTeamAdmins
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      ('MissingPermission
                                                                                                         'Nothing)
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          NewTeamMember
                                                                                                        :> MultiVerb
                                                                                                             'PUT
                                                                                                             '[JSON]
                                                                                                             '[RespondEmpty
                                                                                                                 200
                                                                                                                 ""]
                                                                                                             ())))))))))))))
                                             :<|> (Named
                                                     "user-is-team-owner"
                                                     ("is-team-owner"
                                                      :> (Capture "uid" UserId
                                                          :> (CanThrow 'AccessDenied
                                                              :> (CanThrow 'TeamMemberNotFound
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> MultiVerb
                                                                           'GET
                                                                           '[JSON]
                                                                           '[RespondEmpty
                                                                               200
                                                                               "User is team owner"]
                                                                           ())))))
                                                   :<|> ("search-visibility"
                                                         :> (Named
                                                               "get-search-visibility-internal"
                                                               (Get
                                                                  '[JSON] TeamSearchVisibilityView)
                                                             :<|> Named
                                                                    "set-search-visibility-internal"
                                                                    (CanThrow
                                                                       'TeamSearchVisibilityNotEnabled
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       TeamSearchVisibilityView
                                                                                     :> MultiVerb
                                                                                          'PUT
                                                                                          '[JSON]
                                                                                          '[RespondEmpty
                                                                                              204
                                                                                              "OK"]
                                                                                          ()))))))))))))))))
      :<|> ((Named
               "get-team-members"
               (CanThrow 'NonBindingTeam
                :> (CanThrow 'TeamNotFound
                    :> ("users"
                        :> (Capture "uid" UserId
                            :> ("team" :> ("members" :> Get '[JSON] TeamMemberList))))))
             :<|> (Named
                     "get-team-id"
                     (CanThrow 'NonBindingTeam
                      :> (CanThrow 'TeamNotFound
                          :> ("users"
                              :> (Capture "uid" UserId :> ("team" :> Get '[JSON] TeamId)))))
                   :<|> (Named
                           "test-get-clients"
                           ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
                         :<|> (Named
                                 "test-add-client"
                                 ("clients"
                                  :> (ZUser
                                      :> (Capture "cid" ClientId
                                          :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
                               :<|> (Named
                                       "test-delete-client"
                                       ("clients"
                                        :> (ZUser
                                            :> (Capture "cid" ClientId
                                                :> MultiVerb
                                                     'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
                                     :<|> (Named
                                             "add-service"
                                             ("services"
                                              :> (ReqBody '[JSON] Service
                                                  :> MultiVerb
                                                       'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
                                           :<|> (Named
                                                   "delete-service"
                                                   ("services"
                                                    :> (ReqBody '[JSON] ServiceRef
                                                        :> MultiVerb
                                                             'DELETE
                                                             '[JSON]
                                                             '[RespondEmpty 200 "OK"]
                                                             ()))
                                                 :<|> (Named
                                                         "i-add-bot"
                                                         (CanThrow
                                                            ('ActionDenied 'AddConversationMember)
                                                          :> (CanThrow 'ConvNotFound
                                                              :> (CanThrow 'InvalidOperation
                                                                  :> (CanThrow 'TooManyMembers
                                                                      :> ("bots"
                                                                          :> (ZLocalUser
                                                                              :> (ZConn
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        AddBot
                                                                                      :> Post
                                                                                           '[JSON]
                                                                                           Event))))))))
                                                       :<|> (Named
                                                               "delete-bot"
                                                               (CanThrow 'ConvNotFound
                                                                :> (CanThrow
                                                                      ('ActionDenied
                                                                         'RemoveConversationMember)
                                                                    :> ("bots"
                                                                        :> (ZLocalUser
                                                                            :> (ZOptConn
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      RemoveBot
                                                                                    :> MultiVerb
                                                                                         'DELETE
                                                                                         '[JSON]
                                                                                         (UpdateResponses
                                                                                            "Bot not found"
                                                                                            "Bot deleted"
                                                                                            Event)
                                                                                         (UpdateResult
                                                                                            Event)))))))
                                                             :<|> (Named
                                                                     "put-custom-backend"
                                                                     ("custom-backend"
                                                                      :> ("by-domain"
                                                                          :> (Capture
                                                                                "domain" Domain
                                                                              :> (ReqBody
                                                                                    '[JSON]
                                                                                    CustomBackend
                                                                                  :> MultiVerb
                                                                                       'PUT
                                                                                       '[JSON]
                                                                                       '[RespondEmpty
                                                                                           201 "OK"]
                                                                                       ()))))
                                                                   :<|> Named
                                                                          "delete-custom-backend"
                                                                          ("custom-backend"
                                                                           :> ("by-domain"
                                                                               :> (Capture
                                                                                     "domain" Domain
                                                                                   :> MultiVerb
                                                                                        'DELETE
                                                                                        '[JSON]
                                                                                        '[RespondEmpty
                                                                                            200
                                                                                            "OK"]
                                                                                        ())))))))))))))
            :<|> (Named
                    "upsert-one2one"
                    (Summary "Create or Update a connect or one2one conversation."
                     :> ("conversations"
                         :> ("one2one"
                             :> ("upsert"
                                 :> (ReqBody '[JSON] UpsertOne2OneConversationRequest
                                     :> MultiVerb
                                          'POST
                                          '[JSON]
                                          '[RespondEmpty 200 "Upsert One2One Policy"]
                                          ())))))
                  :<|> ((((Named
                             '("iget", LegalholdConfig)
                             (Description ""
                              :> (Summary "Get config for legalhold"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("legalhold"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      LegalholdConfig))))))))))
                           :<|> (Named
                                   '("iput", LegalholdConfig)
                                   (Description ""
                                    :> (Summary "Put config for legalhold"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> (CanThrow TeamFeatureError
                                                        :> (CanThrowMany
                                                              '[ 'ActionDenied
                                                                   'RemoveConversationMember,
                                                                 'CannotEnableLegalHoldServiceLargeTeam,
                                                                 'LegalHoldNotEnabled,
                                                                 'LegalHoldDisableUnimplemented,
                                                                 'LegalHoldServiceNotRegistered,
                                                                 'UserLegalHoldIllegalOperation,
                                                                 'LegalHoldCouldNotBlockConnections]
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("legalhold"
                                                                            :> (ReqBody
                                                                                  '[JSON]
                                                                                  (Feature
                                                                                     LegalholdConfig)
                                                                                :> Put
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        LegalholdConfig)))))))))))))
                                 :<|> Named
                                        '("ipatch", LegalholdConfig)
                                        (Description ""
                                         :> (Summary "Patch config for legalhold"
                                             :> (CanThrow ('MissingPermission 'Nothing)
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany
                                                                   '[ 'ActionDenied
                                                                        'RemoveConversationMember,
                                                                      'CannotEnableLegalHoldServiceLargeTeam,
                                                                      'LegalHoldNotEnabled,
                                                                      'LegalHoldDisableUnimplemented,
                                                                      'LegalHoldServiceNotRegistered,
                                                                      'UserLegalHoldIllegalOperation,
                                                                      'LegalHoldCouldNotBlockConnections]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("legalhold"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (LockableFeaturePatch
                                                                                          LegalholdConfig)
                                                                                     :> Patch
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             LegalholdConfig)))))))))))))))
                          :<|> ((Named
                                   '("iget", SSOConfig)
                                   (Description ""
                                    :> (Summary "Get config for sso"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("sso"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            SSOConfig))))))))))
                                 :<|> (Named
                                         '("iput", SSOConfig)
                                         (Description ""
                                          :> (Summary "Put config for sso"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow TeamFeatureError
                                                              :> (CanThrowMany '[]
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("sso"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        (Feature
                                                                                           SSOConfig)
                                                                                      :> Put
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              SSOConfig)))))))))))))
                                       :<|> Named
                                              '("ipatch", SSOConfig)
                                              (Description ""
                                               :> (Summary "Patch config for sso"
                                                   :> (CanThrow ('MissingPermission 'Nothing)
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("sso"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (LockableFeaturePatch
                                                                                                SSOConfig)
                                                                                           :> Patch
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   SSOConfig)))))))))))))))
                                :<|> ((Named
                                         '("iget", SearchVisibilityAvailableConfig)
                                         (Description ""
                                          :> (Summary "Get config for searchVisibility"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("searchVisibility"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  SearchVisibilityAvailableConfig))))))))))
                                       :<|> (Named
                                               '("iput", SearchVisibilityAvailableConfig)
                                               (Description ""
                                                :> (Summary "Put config for searchVisibility"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> (CanThrowMany '[]
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("searchVisibility"
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              (Feature
                                                                                                 SearchVisibilityAvailableConfig)
                                                                                            :> Put
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    SearchVisibilityAvailableConfig)))))))))))))
                                             :<|> Named
                                                    '("ipatch", SearchVisibilityAvailableConfig)
                                                    (Description ""
                                                     :> (Summary "Patch config for searchVisibility"
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("searchVisibility"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (LockableFeaturePatch
                                                                                                      SearchVisibilityAvailableConfig)
                                                                                                 :> Patch
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         SearchVisibilityAvailableConfig)))))))))))))))
                                      :<|> ((Named
                                               '("iget", SearchVisibilityInboundConfig)
                                               (Description ""
                                                :> (Summary "Get config for searchVisibilityInbound"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("searchVisibilityInbound"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SearchVisibilityInboundConfig))))))))))
                                             :<|> (Named
                                                     '("iput", SearchVisibilityInboundConfig)
                                                     (Description ""
                                                      :> (Summary
                                                            "Put config for searchVisibilityInbound"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany '[]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("searchVisibilityInbound"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (Feature
                                                                                                       SearchVisibilityInboundConfig)
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          SearchVisibilityInboundConfig)))))))))))))
                                                   :<|> Named
                                                          '("ipatch", SearchVisibilityInboundConfig)
                                                          (Description ""
                                                           :> (Summary
                                                                 "Patch config for searchVisibilityInbound"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("searchVisibilityInbound"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (LockableFeaturePatch
                                                                                                            SearchVisibilityInboundConfig)
                                                                                                       :> Patch
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               SearchVisibilityInboundConfig)))))))))))))))
                                            :<|> ((Named
                                                     '("iget", ValidateSAMLEmailsConfig)
                                                     (Description ""
                                                      :> (Summary
                                                            "Get config for validateSAMLemails"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("validateSAMLemails"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              ValidateSAMLEmailsConfig))))))))))
                                                   :<|> (Named
                                                           '("iput", ValidateSAMLEmailsConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Put config for validateSAMLemails"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("validateSAMLemails"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             ValidateSAMLEmailsConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                ValidateSAMLEmailsConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch",
                                                                  ValidateSAMLEmailsConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Patch config for validateSAMLemails"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("validateSAMLemails"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  ValidateSAMLEmailsConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     ValidateSAMLEmailsConfig)))))))))))))))
                                                  :<|> ((Named
                                                           '("iget", DigitalSignaturesConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Get config for digitalSignatures"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("digitalSignatures"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    DigitalSignaturesConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput", DigitalSignaturesConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Put config for digitalSignatures"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("digitalSignatures"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   DigitalSignaturesConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      DigitalSignaturesConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch",
                                                                        DigitalSignaturesConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for digitalSignatures"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("digitalSignatures"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        DigitalSignaturesConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           DigitalSignaturesConfig)))))))))))))))
                                                        :<|> ((Named
                                                                 '("iget", AppLockConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Get config for appLock"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("appLock"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          AppLockConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput", AppLockConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for appLock"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("appLock"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         AppLockConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            AppLockConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch",
                                                                              AppLockConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for appLock"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("appLock"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              AppLockConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 AppLockConfig)))))))))))))))
                                                              :<|> ((Named
                                                                       '("iget", FileSharingConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for fileSharing"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("fileSharing"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                FileSharingConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               FileSharingConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for fileSharing"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("fileSharing"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               FileSharingConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  FileSharingConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    FileSharingConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for fileSharing"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("fileSharing"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    FileSharingConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       FileSharingConfig)))))))))))))))
                                                                    :<|> (Named
                                                                            '("iget",
                                                                              ClassifiedDomainsConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Get config for classifiedDomains"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("classifiedDomains"
                                                                                                             :> Get
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     ClassifiedDomainsConfig))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     ConferenceCallingConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for conferenceCalling"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("conferenceCalling"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            ConferenceCallingConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           ConferenceCallingConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for conferenceCalling"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("conferenceCalling"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           ConferenceCallingConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              ConferenceCallingConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                ConferenceCallingConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for conferenceCalling"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("conferenceCalling"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                ConferenceCallingConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   ConferenceCallingConfig)))))))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           SelfDeletingMessagesConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for selfDeletingMessages"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("selfDeletingMessages"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  SelfDeletingMessagesConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 SelfDeletingMessagesConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for selfDeletingMessages"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("selfDeletingMessages"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 SelfDeletingMessagesConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    SelfDeletingMessagesConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      SelfDeletingMessagesConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for selfDeletingMessages"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("selfDeletingMessages"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      SelfDeletingMessagesConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         SelfDeletingMessagesConfig)))))))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 GuestLinksConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for conversationGuestLinks"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("conversationGuestLinks"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        GuestLinksConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       GuestLinksConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for conversationGuestLinks"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("conversationGuestLinks"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       GuestLinksConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          GuestLinksConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            GuestLinksConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for conversationGuestLinks"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("conversationGuestLinks"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            GuestLinksConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               GuestLinksConfig)))))))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       SndFactorPasswordChallengeConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for sndFactorPasswordChallenge"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("sndFactorPasswordChallenge"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              SndFactorPasswordChallengeConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             SndFactorPasswordChallengeConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for sndFactorPasswordChallenge"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("sndFactorPasswordChallenge"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             SndFactorPasswordChallengeConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                SndFactorPasswordChallengeConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for sndFactorPasswordChallenge"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("sndFactorPasswordChallenge"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             MLSConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for mls"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("mls"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    MLSConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   MLSConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for mls"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("mls"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   MLSConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      MLSConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        MLSConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for mls"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("mls"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        MLSConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           MLSConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         OutlookCalIntegrationConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for outlookCalIntegration"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("outlookCalIntegration"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                OutlookCalIntegrationConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               OutlookCalIntegrationConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for outlookCalIntegration"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("outlookCalIntegration"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               OutlookCalIntegrationConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  OutlookCalIntegrationConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    OutlookCalIntegrationConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for outlookCalIntegration"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("outlookCalIntegration"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    OutlookCalIntegrationConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       OutlookCalIntegrationConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               MlsE2EIdConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for mlsE2EId"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("mlsE2EId"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      MlsE2EIdConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     MlsE2EIdConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for mlsE2EId"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("mlsE2EId"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     MlsE2EIdConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        MlsE2EIdConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          MlsE2EIdConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for mlsE2EId"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("mlsE2EId"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          MlsE2EIdConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             MlsE2EIdConfig)))))))))))))))
                                                                                                                          :<|> ((Named
                                                                                                                                   '("iget",
                                                                                                                                     MlsMigrationConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for mlsMigration"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("mlsMigration"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MlsMigrationConfig))))))))))
                                                                                                                                 :<|> (Named
                                                                                                                                         '("iput",
                                                                                                                                           MlsMigrationConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Put config for mlsMigration"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("mlsMigration"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Feature
                                                                                                                                                                                           MlsMigrationConfig)
                                                                                                                                                                                      :> Put
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              MlsMigrationConfig)))))))))))))
                                                                                                                                       :<|> Named
                                                                                                                                              '("ipatch",
                                                                                                                                                MlsMigrationConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Patch config for mlsMigration"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("mlsMigration"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                MlsMigrationConfig)
                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   MlsMigrationConfig)))))))))))))))
                                                                                                                                :<|> ((Named
                                                                                                                                         '("iget",
                                                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                                                         (Description
                                                                                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for enforceFileDownloadLocation"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("enforceFileDownloadLocation"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                       :<|> (Named
                                                                                                                                               '("iput",
                                                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                                                               (Description
                                                                                                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                :> (Summary
                                                                                                                                                      "Put config for enforceFileDownloadLocation"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                          '[]
                                                                                                                                                                        :> ("teams"
                                                                                                                                                                            :> (Capture
                                                                                                                                                                                  "tid"
                                                                                                                                                                                  TeamId
                                                                                                                                                                                :> ("features"
                                                                                                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (Feature
                                                                                                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                                                                                                            :> Put
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                             :<|> Named
                                                                                                                                                    '("ipatch",
                                                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                                                    (Description
                                                                                                                                                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Patch config for enforceFileDownloadLocation"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("enforceFileDownloadLocation"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                 :> Patch
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                      :<|> (Named
                                                                                                                                              '("iget",
                                                                                                                                                LimitedEventFanoutConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Get config for limitedEventFanout"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("teams"
                                                                                                                                                                   :> (Capture
                                                                                                                                                                         "tid"
                                                                                                                                                                         TeamId
                                                                                                                                                                       :> ("features"
                                                                                                                                                                           :> ("limitedEventFanout"
                                                                                                                                                                               :> Get
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       LimitedEventFanoutConfig))))))))))
                                                                                                                                            :<|> (Named
                                                                                                                                                    '("iput",
                                                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                                                    (Description
                                                                                                                                                       ""
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Put config for limitedEventFanout"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("limitedEventFanout"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (Feature
                                                                                                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                                                                                                 :> Put
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         LimitedEventFanoutConfig)))))))))))))
                                                                                                                                                  :<|> Named
                                                                                                                                                         '("ipatch",
                                                                                                                                                           LimitedEventFanoutConfig)
                                                                                                                                                         (Description
                                                                                                                                                            ""
                                                                                                                                                          :> (Summary
                                                                                                                                                                "Patch config for limitedEventFanout"
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    ('MissingPermission
                                                                                                                                                                       'Nothing)
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                TeamFeatureError
                                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                                    '[]
                                                                                                                                                                                  :> ("teams"
                                                                                                                                                                                      :> (Capture
                                                                                                                                                                                            "tid"
                                                                                                                                                                                            TeamId
                                                                                                                                                                                          :> ("features"
                                                                                                                                                                                              :> ("limitedEventFanout"
                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        (LockableFeaturePatch
                                                                                                                                                                                                           LimitedEventFanoutConfig)
                                                                                                                                                                                                      :> Patch
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                                              LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                         :<|> (Named
                                 '("ilock", FileSharingConfig)
                                 (Summary "(Un-)lock fileSharing"
                                  :> (Description ""
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("fileSharing"
                                                              :> (Capture "lockStatus" LockStatus
                                                                  :> Put
                                                                       '[JSON]
                                                                       LockStatusResponse)))))))))
                               :<|> (Named
                                       '("ilock", ConferenceCallingConfig)
                                       (Summary "(Un-)lock conferenceCalling"
                                        :> (Description ""
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("conferenceCalling"
                                                                    :> (Capture
                                                                          "lockStatus" LockStatus
                                                                        :> Put
                                                                             '[JSON]
                                                                             LockStatusResponse)))))))))
                                     :<|> (Named
                                             '("ilock", SelfDeletingMessagesConfig)
                                             (Summary "(Un-)lock selfDeletingMessages"
                                              :> (Description ""
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("selfDeletingMessages"
                                                                          :> (Capture
                                                                                "lockStatus"
                                                                                LockStatus
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   LockStatusResponse)))))))))
                                           :<|> (Named
                                                   '("ilock", GuestLinksConfig)
                                                   (Summary "(Un-)lock conversationGuestLinks"
                                                    :> (Description ""
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("conversationGuestLinks"
                                                                                :> (Capture
                                                                                      "lockStatus"
                                                                                      LockStatus
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         LockStatusResponse)))))))))
                                                 :<|> (Named
                                                         '("ilock",
                                                           SndFactorPasswordChallengeConfig)
                                                         (Summary
                                                            "(Un-)lock sndFactorPasswordChallenge"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("sndFactorPasswordChallenge"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock", MLSConfig)
                                                               (Summary "(Un-)lock mls"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mls"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock",
                                                                       OutlookCalIntegrationConfig)
                                                                     (Summary
                                                                        "(Un-)lock outlookCalIntegration"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("outlookCalIntegration"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock",
                                                                             MlsE2EIdConfig)
                                                                           (Summary
                                                                              "(Un-)lock mlsE2EId"
                                                                            :> (Description ""
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mlsE2EId"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("ilock",
                                                                                   MlsMigrationConfig)
                                                                                 (Summary
                                                                                    "(Un-)lock mlsMigration"
                                                                                  :> (Description ""
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mlsMigration"
                                                                                                              :> (Capture
                                                                                                                    "lockStatus"
                                                                                                                    LockStatus
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       LockStatusResponse)))))))))
                                                                               :<|> (Named
                                                                                       '("ilock",
                                                                                         EnforceFileDownloadLocationConfig)
                                                                                       (Summary
                                                                                          "(Un-)lock enforceFileDownloadLocation"
                                                                                        :> (Description
                                                                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                    :> (Capture
                                                                                                                          "lockStatus"
                                                                                                                          LockStatus
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             LockStatusResponse)))))))))
                                                                                     :<|> (Named
                                                                                             '("igetmulti",
                                                                                               SearchVisibilityInboundConfig)
                                                                                             (Summary
                                                                                                "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                              :> ("features-multi-teams"
                                                                                                  :> ("searchVisibilityInbound"
                                                                                                      :> (ReqBody
                                                                                                            '[JSON]
                                                                                                            TeamFeatureNoConfigMultiRequest
                                                                                                          :> Post
                                                                                                               '[JSON]
                                                                                                               (TeamFeatureNoConfigMultiResponse
                                                                                                                  SearchVisibilityInboundConfig)))))
                                                                                           :<|> Named
                                                                                                  "feature-configs-internal"
                                                                                                  (Summary
                                                                                                     "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                                   :> ("feature-configs"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (QueryParam'
                                                                                                                         '[Optional,
                                                                                                                           Strict,
                                                                                                                           Description
                                                                                                                             "Optional user id"]
                                                                                                                         "user_id"
                                                                                                                         UserId
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            AllTeamFeatures))))))))))))))))))
                        :<|> (IFederationAPI :<|> (IConversationAPI :<|> IEJPDAPI))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
     (("legalhold"
       :> ("whitelisted-teams"
           :> (Capture "tid" TeamId
               :> (Named
                     "set-team-legalhold-whitelisted"
                     (MultiVerb
                        'PUT '[JSON] '[RespondEmpty 200 "Team Legalhold Whitelisted"] ())
                   :<|> (Named
                           "unset-team-legalhold-whitelisted"
                           (MultiVerb
                              'DELETE
                              '[JSON]
                              '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
                              ())
                         :<|> Named
                                "get-team-legalhold-whitelisted"
                                (MultiVerb
                                   'GET
                                   '[JSON]
                                   '[RespondEmpty 404 "Team not Legalhold Whitelisted",
                                     RespondEmpty 200 "Team Legalhold Whitelisted"]
                                   Bool))))))
      :<|> (("teams"
             :> (Capture "tid" TeamId
                 :> (Named
                       "get-team-internal"
                       (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
                     :<|> (Named
                             "create-binding-team"
                             (ZUser
                              :> (ReqBody '[JSON] BindingNewTeam
                                  :> MultiVerb
                                       'PUT
                                       '[JSON]
                                       '[WithHeaders
                                           '[Header "Location" TeamId]
                                           TeamId
                                           (RespondEmpty 201 "OK")]
                                       TeamId))
                           :<|> (Named
                                   "delete-binding-team"
                                   (CanThrow 'NoBindingTeam
                                    :> (CanThrow 'NotAOneMemberTeam
                                        :> (CanThrow 'DeleteQueueFull
                                            :> (CanThrow 'TeamNotFound
                                                :> (QueryFlag "force"
                                                    :> MultiVerb
                                                         'DELETE
                                                         '[JSON]
                                                         '[RespondEmpty 202 "OK"]
                                                         ())))))
                                 :<|> (Named
                                         "get-team-name"
                                         ("name"
                                          :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
                                       :<|> (Named
                                               "update-team-status"
                                               ("status"
                                                :> (CanThrow 'TeamNotFound
                                                    :> (CanThrow 'InvalidTeamStatusUpdate
                                                        :> (ReqBody '[JSON] TeamStatusUpdate
                                                            :> MultiVerb
                                                                 'PUT
                                                                 '[JSON]
                                                                 '[RespondEmpty 200 "OK"]
                                                                 ()))))
                                             :<|> (("members"
                                                    :> (Named
                                                          "unchecked-add-team-member"
                                                          (CanThrow 'TooManyTeamMembers
                                                           :> (CanThrow
                                                                 'TooManyTeamMembersOnTeamWithLegalhold
                                                               :> (CanThrow 'TooManyTeamAdmins
                                                                   :> (ReqBody '[JSON] NewTeamMember
                                                                       :> MultiVerb
                                                                            'POST
                                                                            '[JSON]
                                                                            '[RespondEmpty 200 "OK"]
                                                                            ()))))
                                                        :<|> (Named
                                                                "unchecked-get-team-members"
                                                                (QueryParam'
                                                                   '[Strict]
                                                                   "maxResults"
                                                                   (Range
                                                                      1 HardTruncationLimit Int32)
                                                                 :> Get '[JSON] TeamMemberList)
                                                              :<|> (Named
                                                                      "unchecked-get-team-member"
                                                                      (Capture "uid" UserId
                                                                       :> (CanThrow
                                                                             'TeamMemberNotFound
                                                                           :> Get
                                                                                '[JSON] TeamMember))
                                                                    :<|> (Named
                                                                            "can-user-join-team"
                                                                            ("check"
                                                                             :> (CanThrow
                                                                                   'TooManyTeamMembersOnTeamWithLegalhold
                                                                                 :> MultiVerb
                                                                                      'GET
                                                                                      '[JSON]
                                                                                      '[RespondEmpty
                                                                                          200
                                                                                          "User can join"]
                                                                                      ()))
                                                                          :<|> Named
                                                                                 "unchecked-update-team-member"
                                                                                 (CanThrow
                                                                                    'AccessDenied
                                                                                  :> (CanThrow
                                                                                        'InvalidPermissions
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> (CanThrow
                                                                                                'TeamMemberNotFound
                                                                                              :> (CanThrow
                                                                                                    'TooManyTeamAdmins
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            ('MissingPermission
                                                                                                               'Nothing)
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                NewTeamMember
                                                                                                              :> MultiVerb
                                                                                                                   'PUT
                                                                                                                   '[JSON]
                                                                                                                   '[RespondEmpty
                                                                                                                       200
                                                                                                                       ""]
                                                                                                                   ())))))))))))))
                                                   :<|> (Named
                                                           "user-is-team-owner"
                                                           ("is-team-owner"
                                                            :> (Capture "uid" UserId
                                                                :> (CanThrow 'AccessDenied
                                                                    :> (CanThrow 'TeamMemberNotFound
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> MultiVerb
                                                                                 'GET
                                                                                 '[JSON]
                                                                                 '[RespondEmpty
                                                                                     200
                                                                                     "User is team owner"]
                                                                                 ())))))
                                                         :<|> ("search-visibility"
                                                               :> (Named
                                                                     "get-search-visibility-internal"
                                                                     (Get
                                                                        '[JSON]
                                                                        TeamSearchVisibilityView)
                                                                   :<|> Named
                                                                          "set-search-visibility-internal"
                                                                          (CanThrow
                                                                             'TeamSearchVisibilityNotEnabled
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             TeamSearchVisibilityView
                                                                                           :> MultiVerb
                                                                                                'PUT
                                                                                                '[JSON]
                                                                                                '[RespondEmpty
                                                                                                    204
                                                                                                    "OK"]
                                                                                                ()))))))))))))))))
            :<|> ((Named
                     "get-team-members"
                     (CanThrow 'NonBindingTeam
                      :> (CanThrow 'TeamNotFound
                          :> ("users"
                              :> (Capture "uid" UserId
                                  :> ("team" :> ("members" :> Get '[JSON] TeamMemberList))))))
                   :<|> (Named
                           "get-team-id"
                           (CanThrow 'NonBindingTeam
                            :> (CanThrow 'TeamNotFound
                                :> ("users"
                                    :> (Capture "uid" UserId :> ("team" :> Get '[JSON] TeamId)))))
                         :<|> (Named
                                 "test-get-clients"
                                 ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
                               :<|> (Named
                                       "test-add-client"
                                       ("clients"
                                        :> (ZUser
                                            :> (Capture "cid" ClientId
                                                :> MultiVerb
                                                     'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
                                     :<|> (Named
                                             "test-delete-client"
                                             ("clients"
                                              :> (ZUser
                                                  :> (Capture "cid" ClientId
                                                      :> MultiVerb
                                                           'DELETE
                                                           '[JSON]
                                                           '[RespondEmpty 200 "OK"]
                                                           ())))
                                           :<|> (Named
                                                   "add-service"
                                                   ("services"
                                                    :> (ReqBody '[JSON] Service
                                                        :> MultiVerb
                                                             'POST
                                                             '[JSON]
                                                             '[RespondEmpty 200 "OK"]
                                                             ()))
                                                 :<|> (Named
                                                         "delete-service"
                                                         ("services"
                                                          :> (ReqBody '[JSON] ServiceRef
                                                              :> MultiVerb
                                                                   'DELETE
                                                                   '[JSON]
                                                                   '[RespondEmpty 200 "OK"]
                                                                   ()))
                                                       :<|> (Named
                                                               "i-add-bot"
                                                               (CanThrow
                                                                  ('ActionDenied
                                                                     'AddConversationMember)
                                                                :> (CanThrow 'ConvNotFound
                                                                    :> (CanThrow 'InvalidOperation
                                                                        :> (CanThrow 'TooManyMembers
                                                                            :> ("bots"
                                                                                :> (ZLocalUser
                                                                                    :> (ZConn
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              AddBot
                                                                                            :> Post
                                                                                                 '[JSON]
                                                                                                 Event))))))))
                                                             :<|> (Named
                                                                     "delete-bot"
                                                                     (CanThrow 'ConvNotFound
                                                                      :> (CanThrow
                                                                            ('ActionDenied
                                                                               'RemoveConversationMember)
                                                                          :> ("bots"
                                                                              :> (ZLocalUser
                                                                                  :> (ZOptConn
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            RemoveBot
                                                                                          :> MultiVerb
                                                                                               'DELETE
                                                                                               '[JSON]
                                                                                               (UpdateResponses
                                                                                                  "Bot not found"
                                                                                                  "Bot deleted"
                                                                                                  Event)
                                                                                               (UpdateResult
                                                                                                  Event)))))))
                                                                   :<|> (Named
                                                                           "put-custom-backend"
                                                                           ("custom-backend"
                                                                            :> ("by-domain"
                                                                                :> (Capture
                                                                                      "domain"
                                                                                      Domain
                                                                                    :> (ReqBody
                                                                                          '[JSON]
                                                                                          CustomBackend
                                                                                        :> MultiVerb
                                                                                             'PUT
                                                                                             '[JSON]
                                                                                             '[RespondEmpty
                                                                                                 201
                                                                                                 "OK"]
                                                                                             ()))))
                                                                         :<|> Named
                                                                                "delete-custom-backend"
                                                                                ("custom-backend"
                                                                                 :> ("by-domain"
                                                                                     :> (Capture
                                                                                           "domain"
                                                                                           Domain
                                                                                         :> MultiVerb
                                                                                              'DELETE
                                                                                              '[JSON]
                                                                                              '[RespondEmpty
                                                                                                  200
                                                                                                  "OK"]
                                                                                              ())))))))))))))
                  :<|> (Named
                          "upsert-one2one"
                          (Summary "Create or Update a connect or one2one conversation."
                           :> ("conversations"
                               :> ("one2one"
                                   :> ("upsert"
                                       :> (ReqBody '[JSON] UpsertOne2OneConversationRequest
                                           :> MultiVerb
                                                'POST
                                                '[JSON]
                                                '[RespondEmpty 200 "Upsert One2One Policy"]
                                                ())))))
                        :<|> ((((Named
                                   '("iget", LegalholdConfig)
                                   (Description ""
                                    :> (Summary "Get config for legalhold"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("legalhold"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            LegalholdConfig))))))))))
                                 :<|> (Named
                                         '("iput", LegalholdConfig)
                                         (Description ""
                                          :> (Summary "Put config for legalhold"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow TeamFeatureError
                                                              :> (CanThrowMany
                                                                    '[ 'ActionDenied
                                                                         'RemoveConversationMember,
                                                                       'CannotEnableLegalHoldServiceLargeTeam,
                                                                       'LegalHoldNotEnabled,
                                                                       'LegalHoldDisableUnimplemented,
                                                                       'LegalHoldServiceNotRegistered,
                                                                       'UserLegalHoldIllegalOperation,
                                                                       'LegalHoldCouldNotBlockConnections]
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("legalhold"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        (Feature
                                                                                           LegalholdConfig)
                                                                                      :> Put
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              LegalholdConfig)))))))))))))
                                       :<|> Named
                                              '("ipatch", LegalholdConfig)
                                              (Description ""
                                               :> (Summary "Patch config for legalhold"
                                                   :> (CanThrow ('MissingPermission 'Nothing)
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany
                                                                         '[ 'ActionDenied
                                                                              'RemoveConversationMember,
                                                                            'CannotEnableLegalHoldServiceLargeTeam,
                                                                            'LegalHoldNotEnabled,
                                                                            'LegalHoldDisableUnimplemented,
                                                                            'LegalHoldServiceNotRegistered,
                                                                            'UserLegalHoldIllegalOperation,
                                                                            'LegalHoldCouldNotBlockConnections]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("legalhold"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (LockableFeaturePatch
                                                                                                LegalholdConfig)
                                                                                           :> Patch
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   LegalholdConfig)))))))))))))))
                                :<|> ((Named
                                         '("iget", SSOConfig)
                                         (Description ""
                                          :> (Summary "Get config for sso"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("sso"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  SSOConfig))))))))))
                                       :<|> (Named
                                               '("iput", SSOConfig)
                                               (Description ""
                                                :> (Summary "Put config for sso"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> (CanThrowMany '[]
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("sso"
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              (Feature
                                                                                                 SSOConfig)
                                                                                            :> Put
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    SSOConfig)))))))))))))
                                             :<|> Named
                                                    '("ipatch", SSOConfig)
                                                    (Description ""
                                                     :> (Summary "Patch config for sso"
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("sso"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (LockableFeaturePatch
                                                                                                      SSOConfig)
                                                                                                 :> Patch
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         SSOConfig)))))))))))))))
                                      :<|> ((Named
                                               '("iget", SearchVisibilityAvailableConfig)
                                               (Description ""
                                                :> (Summary "Get config for searchVisibility"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("searchVisibility"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SearchVisibilityAvailableConfig))))))))))
                                             :<|> (Named
                                                     '("iput", SearchVisibilityAvailableConfig)
                                                     (Description ""
                                                      :> (Summary "Put config for searchVisibility"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany '[]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("searchVisibility"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (Feature
                                                                                                       SearchVisibilityAvailableConfig)
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          SearchVisibilityAvailableConfig)))))))))))))
                                                   :<|> Named
                                                          '("ipatch",
                                                            SearchVisibilityAvailableConfig)
                                                          (Description ""
                                                           :> (Summary
                                                                 "Patch config for searchVisibility"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("searchVisibility"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (LockableFeaturePatch
                                                                                                            SearchVisibilityAvailableConfig)
                                                                                                       :> Patch
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               SearchVisibilityAvailableConfig)))))))))))))))
                                            :<|> ((Named
                                                     '("iget", SearchVisibilityInboundConfig)
                                                     (Description ""
                                                      :> (Summary
                                                            "Get config for searchVisibilityInbound"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("searchVisibilityInbound"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              SearchVisibilityInboundConfig))))))))))
                                                   :<|> (Named
                                                           '("iput", SearchVisibilityInboundConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Put config for searchVisibilityInbound"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("searchVisibilityInbound"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             SearchVisibilityInboundConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SearchVisibilityInboundConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch",
                                                                  SearchVisibilityInboundConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Patch config for searchVisibilityInbound"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("searchVisibilityInbound"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  SearchVisibilityInboundConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     SearchVisibilityInboundConfig)))))))))))))))
                                                  :<|> ((Named
                                                           '("iget", ValidateSAMLEmailsConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Get config for validateSAMLemails"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("validateSAMLemails"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    ValidateSAMLEmailsConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput", ValidateSAMLEmailsConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Put config for validateSAMLemails"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("validateSAMLemails"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   ValidateSAMLEmailsConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      ValidateSAMLEmailsConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch",
                                                                        ValidateSAMLEmailsConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for validateSAMLemails"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("validateSAMLemails"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        ValidateSAMLEmailsConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           ValidateSAMLEmailsConfig)))))))))))))))
                                                        :<|> ((Named
                                                                 '("iget", DigitalSignaturesConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Get config for digitalSignatures"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("digitalSignatures"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          DigitalSignaturesConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput",
                                                                         DigitalSignaturesConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for digitalSignatures"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("digitalSignatures"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         DigitalSignaturesConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            DigitalSignaturesConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch",
                                                                              DigitalSignaturesConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for digitalSignatures"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("digitalSignatures"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              DigitalSignaturesConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 DigitalSignaturesConfig)))))))))))))))
                                                              :<|> ((Named
                                                                       '("iget", AppLockConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for appLock"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("appLock"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                AppLockConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               AppLockConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for appLock"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("appLock"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               AppLockConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  AppLockConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    AppLockConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for appLock"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("appLock"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    AppLockConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       AppLockConfig)))))))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               FileSharingConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for fileSharing"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("fileSharing"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      FileSharingConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     FileSharingConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for fileSharing"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("fileSharing"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     FileSharingConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        FileSharingConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          FileSharingConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for fileSharing"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("fileSharing"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          FileSharingConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             FileSharingConfig)))))))))))))))
                                                                          :<|> (Named
                                                                                  '("iget",
                                                                                    ClassifiedDomainsConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Get config for classifiedDomains"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("classifiedDomains"
                                                                                                                   :> Get
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           ClassifiedDomainsConfig))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           ConferenceCallingConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for conferenceCalling"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("conferenceCalling"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  ConferenceCallingConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 ConferenceCallingConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for conferenceCalling"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("conferenceCalling"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 ConferenceCallingConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    ConferenceCallingConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      ConferenceCallingConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for conferenceCalling"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("conferenceCalling"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      ConferenceCallingConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         ConferenceCallingConfig)))))))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 SelfDeletingMessagesConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for selfDeletingMessages"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("selfDeletingMessages"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        SelfDeletingMessagesConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       SelfDeletingMessagesConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for selfDeletingMessages"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("selfDeletingMessages"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       SelfDeletingMessagesConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          SelfDeletingMessagesConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            SelfDeletingMessagesConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for selfDeletingMessages"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("selfDeletingMessages"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            SelfDeletingMessagesConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               SelfDeletingMessagesConfig)))))))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       GuestLinksConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for conversationGuestLinks"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("conversationGuestLinks"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              GuestLinksConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             GuestLinksConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for conversationGuestLinks"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("conversationGuestLinks"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             GuestLinksConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                GuestLinksConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  GuestLinksConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for conversationGuestLinks"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  GuestLinksConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     GuestLinksConfig)))))))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             SndFactorPasswordChallengeConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for sndFactorPasswordChallenge"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("sndFactorPasswordChallenge"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    SndFactorPasswordChallengeConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   SndFactorPasswordChallengeConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for sndFactorPasswordChallenge"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("sndFactorPasswordChallenge"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   SndFactorPasswordChallengeConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      SndFactorPasswordChallengeConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        SndFactorPasswordChallengeConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for sndFactorPasswordChallenge"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        SndFactorPasswordChallengeConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   MLSConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for mls"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("mls"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          MLSConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         MLSConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for mls"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("mls"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         MLSConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MLSConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              MLSConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for mls"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("mls"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              MLSConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 MLSConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               OutlookCalIntegrationConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for outlookCalIntegration"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("outlookCalIntegration"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      OutlookCalIntegrationConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     OutlookCalIntegrationConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for outlookCalIntegration"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("outlookCalIntegration"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     OutlookCalIntegrationConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        OutlookCalIntegrationConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          OutlookCalIntegrationConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for outlookCalIntegration"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("outlookCalIntegration"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          OutlookCalIntegrationConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             OutlookCalIntegrationConfig)))))))))))))))
                                                                                                                          :<|> ((Named
                                                                                                                                   '("iget",
                                                                                                                                     MlsE2EIdConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for mlsE2EId"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("mlsE2EId"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MlsE2EIdConfig))))))))))
                                                                                                                                 :<|> (Named
                                                                                                                                         '("iput",
                                                                                                                                           MlsE2EIdConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Put config for mlsE2EId"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("mlsE2EId"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Feature
                                                                                                                                                                                           MlsE2EIdConfig)
                                                                                                                                                                                      :> Put
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              MlsE2EIdConfig)))))))))))))
                                                                                                                                       :<|> Named
                                                                                                                                              '("ipatch",
                                                                                                                                                MlsE2EIdConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Patch config for mlsE2EId"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("mlsE2EId"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                MlsE2EIdConfig)
                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   MlsE2EIdConfig)))))))))))))))
                                                                                                                                :<|> ((Named
                                                                                                                                         '("iget",
                                                                                                                                           MlsMigrationConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for mlsMigration"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("mlsMigration"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  MlsMigrationConfig))))))))))
                                                                                                                                       :<|> (Named
                                                                                                                                               '("iput",
                                                                                                                                                 MlsMigrationConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Put config for mlsMigration"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                          '[]
                                                                                                                                                                        :> ("teams"
                                                                                                                                                                            :> (Capture
                                                                                                                                                                                  "tid"
                                                                                                                                                                                  TeamId
                                                                                                                                                                                :> ("features"
                                                                                                                                                                                    :> ("mlsMigration"
                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (Feature
                                                                                                                                                                                                 MlsMigrationConfig)
                                                                                                                                                                                            :> Put
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    MlsMigrationConfig)))))))))))))
                                                                                                                                             :<|> Named
                                                                                                                                                    '("ipatch",
                                                                                                                                                      MlsMigrationConfig)
                                                                                                                                                    (Description
                                                                                                                                                       ""
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Patch config for mlsMigration"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("mlsMigration"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                                                      MlsMigrationConfig)
                                                                                                                                                                                                 :> Patch
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         MlsMigrationConfig)))))))))))))))
                                                                                                                                      :<|> ((Named
                                                                                                                                               '("iget",
                                                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                                                               (Description
                                                                                                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                :> (Summary
                                                                                                                                                      "Get config for enforceFileDownloadLocation"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                             :<|> (Named
                                                                                                                                                     '("iput",
                                                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                                                     (Description
                                                                                                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Put config for enforceFileDownloadLocation"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                ('MissingPermission
                                                                                                                                                                   'Nothing)
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                          :> (CanThrowMany
                                                                                                                                                                                '[]
                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                        "tid"
                                                                                                                                                                                        TeamId
                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (Feature
                                                                                                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                  :> Put
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                                   :<|> Named
                                                                                                                                                          '("ipatch",
                                                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                                                          (Description
                                                                                                                                                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Patch config for enforceFileDownloadLocation"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('MissingPermission
                                                                                                                                                                        'Nothing)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 TeamFeatureError
                                                                                                                                                                               :> (CanThrowMany
                                                                                                                                                                                     '[]
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                       :> Patch
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                            :<|> (Named
                                                                                                                                                    '("iget",
                                                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                                                    (Description
                                                                                                                                                       ""
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Get config for limitedEventFanout"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("teams"
                                                                                                                                                                         :> (Capture
                                                                                                                                                                               "tid"
                                                                                                                                                                               TeamId
                                                                                                                                                                             :> ("features"
                                                                                                                                                                                 :> ("limitedEventFanout"
                                                                                                                                                                                     :> Get
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             LimitedEventFanoutConfig))))))))))
                                                                                                                                                  :<|> (Named
                                                                                                                                                          '("iput",
                                                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                                                          (Description
                                                                                                                                                             ""
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Put config for limitedEventFanout"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('MissingPermission
                                                                                                                                                                        'Nothing)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 TeamFeatureError
                                                                                                                                                                               :> (CanThrowMany
                                                                                                                                                                                     '[]
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> ("limitedEventFanout"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (Feature
                                                                                                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                                                                                                       :> Put
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               LimitedEventFanoutConfig)))))))))))))
                                                                                                                                                        :<|> Named
                                                                                                                                                               '("ipatch",
                                                                                                                                                                 LimitedEventFanoutConfig)
                                                                                                                                                               (Description
                                                                                                                                                                  ""
                                                                                                                                                                :> (Summary
                                                                                                                                                                      "Patch config for limitedEventFanout"
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          ('MissingPermission
                                                                                                                                                                             'Nothing)
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                                          '[]
                                                                                                                                                                                        :> ("teams"
                                                                                                                                                                                            :> (Capture
                                                                                                                                                                                                  "tid"
                                                                                                                                                                                                  TeamId
                                                                                                                                                                                                :> ("features"
                                                                                                                                                                                                    :> ("limitedEventFanout"
                                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              (LockableFeaturePatch
                                                                                                                                                                                                                 LimitedEventFanoutConfig)
                                                                                                                                                                                                            :> Patch
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                                    LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                               :<|> (Named
                                       '("ilock", FileSharingConfig)
                                       (Summary "(Un-)lock fileSharing"
                                        :> (Description ""
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("fileSharing"
                                                                    :> (Capture
                                                                          "lockStatus" LockStatus
                                                                        :> Put
                                                                             '[JSON]
                                                                             LockStatusResponse)))))))))
                                     :<|> (Named
                                             '("ilock", ConferenceCallingConfig)
                                             (Summary "(Un-)lock conferenceCalling"
                                              :> (Description ""
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("conferenceCalling"
                                                                          :> (Capture
                                                                                "lockStatus"
                                                                                LockStatus
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   LockStatusResponse)))))))))
                                           :<|> (Named
                                                   '("ilock", SelfDeletingMessagesConfig)
                                                   (Summary "(Un-)lock selfDeletingMessages"
                                                    :> (Description ""
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("selfDeletingMessages"
                                                                                :> (Capture
                                                                                      "lockStatus"
                                                                                      LockStatus
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         LockStatusResponse)))))))))
                                                 :<|> (Named
                                                         '("ilock", GuestLinksConfig)
                                                         (Summary "(Un-)lock conversationGuestLinks"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("conversationGuestLinks"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock",
                                                                 SndFactorPasswordChallengeConfig)
                                                               (Summary
                                                                  "(Un-)lock sndFactorPasswordChallenge"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("sndFactorPasswordChallenge"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock", MLSConfig)
                                                                     (Summary "(Un-)lock mls"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mls"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock",
                                                                             OutlookCalIntegrationConfig)
                                                                           (Summary
                                                                              "(Un-)lock outlookCalIntegration"
                                                                            :> (Description ""
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("outlookCalIntegration"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("ilock",
                                                                                   MlsE2EIdConfig)
                                                                                 (Summary
                                                                                    "(Un-)lock mlsE2EId"
                                                                                  :> (Description ""
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mlsE2EId"
                                                                                                              :> (Capture
                                                                                                                    "lockStatus"
                                                                                                                    LockStatus
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       LockStatusResponse)))))))))
                                                                               :<|> (Named
                                                                                       '("ilock",
                                                                                         MlsMigrationConfig)
                                                                                       (Summary
                                                                                          "(Un-)lock mlsMigration"
                                                                                        :> (Description
                                                                                              ""
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mlsMigration"
                                                                                                                    :> (Capture
                                                                                                                          "lockStatus"
                                                                                                                          LockStatus
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             LockStatusResponse)))))))))
                                                                                     :<|> (Named
                                                                                             '("ilock",
                                                                                               EnforceFileDownloadLocationConfig)
                                                                                             (Summary
                                                                                                "(Un-)lock enforceFileDownloadLocation"
                                                                                              :> (Description
                                                                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("enforceFileDownloadLocation"
                                                                                                                          :> (Capture
                                                                                                                                "lockStatus"
                                                                                                                                LockStatus
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   LockStatusResponse)))))))))
                                                                                           :<|> (Named
                                                                                                   '("igetmulti",
                                                                                                     SearchVisibilityInboundConfig)
                                                                                                   (Summary
                                                                                                      "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                                    :> ("features-multi-teams"
                                                                                                        :> ("searchVisibilityInbound"
                                                                                                            :> (ReqBody
                                                                                                                  '[JSON]
                                                                                                                  TeamFeatureNoConfigMultiRequest
                                                                                                                :> Post
                                                                                                                     '[JSON]
                                                                                                                     (TeamFeatureNoConfigMultiResponse
                                                                                                                        SearchVisibilityInboundConfig)))))
                                                                                                 :<|> Named
                                                                                                        "feature-configs-internal"
                                                                                                        (Summary
                                                                                                           "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                                         :> ("feature-configs"
                                                                                                             :> (CanThrow
                                                                                                                   ('MissingPermission
                                                                                                                      'Nothing)
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (QueryParam'
                                                                                                                               '[Optional,
                                                                                                                                 Strict,
                                                                                                                                 Description
                                                                                                                                   "Optional user id"]
                                                                                                                               "user_id"
                                                                                                                               UserId
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  AllTeamFeatures))))))))))))))))))
                              :<|> (IFederationAPI :<|> (IConversationAPI :<|> IEJPDAPI)))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  ("teams"
   :> (Capture "tid" TeamId
       :> (Named
             "get-team-internal"
             (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
           :<|> (Named
                   "create-binding-team"
                   (ZUser
                    :> (ReqBody '[JSON] BindingNewTeam
                        :> MultiVerb
                             'PUT
                             '[JSON]
                             '[WithHeaders
                                 '[Header "Location" TeamId] TeamId (RespondEmpty 201 "OK")]
                             TeamId))
                 :<|> (Named
                         "delete-binding-team"
                         (CanThrow 'NoBindingTeam
                          :> (CanThrow 'NotAOneMemberTeam
                              :> (CanThrow 'DeleteQueueFull
                                  :> (CanThrow 'TeamNotFound
                                      :> (QueryFlag "force"
                                          :> MultiVerb
                                               'DELETE '[JSON] '[RespondEmpty 202 "OK"] ())))))
                       :<|> (Named
                               "get-team-name"
                               ("name" :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
                             :<|> (Named
                                     "update-team-status"
                                     ("status"
                                      :> (CanThrow 'TeamNotFound
                                          :> (CanThrow 'InvalidTeamStatusUpdate
                                              :> (ReqBody '[JSON] TeamStatusUpdate
                                                  :> MultiVerb
                                                       'PUT '[JSON] '[RespondEmpty 200 "OK"] ()))))
                                   :<|> (("members"
                                          :> (Named
                                                "unchecked-add-team-member"
                                                (CanThrow 'TooManyTeamMembers
                                                 :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                                     :> (CanThrow 'TooManyTeamAdmins
                                                         :> (ReqBody '[JSON] NewTeamMember
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[RespondEmpty 200 "OK"]
                                                                  ()))))
                                              :<|> (Named
                                                      "unchecked-get-team-members"
                                                      (QueryParam'
                                                         '[Strict]
                                                         "maxResults"
                                                         (Range 1 HardTruncationLimit Int32)
                                                       :> Get '[JSON] TeamMemberList)
                                                    :<|> (Named
                                                            "unchecked-get-team-member"
                                                            (Capture "uid" UserId
                                                             :> (CanThrow 'TeamMemberNotFound
                                                                 :> Get '[JSON] TeamMember))
                                                          :<|> (Named
                                                                  "can-user-join-team"
                                                                  ("check"
                                                                   :> (CanThrow
                                                                         'TooManyTeamMembersOnTeamWithLegalhold
                                                                       :> MultiVerb
                                                                            'GET
                                                                            '[JSON]
                                                                            '[RespondEmpty
                                                                                200 "User can join"]
                                                                            ()))
                                                                :<|> Named
                                                                       "unchecked-update-team-member"
                                                                       (CanThrow 'AccessDenied
                                                                        :> (CanThrow
                                                                              'InvalidPermissions
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      'TeamMemberNotFound
                                                                                    :> (CanThrow
                                                                                          'TooManyTeamAdmins
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (ReqBody
                                                                                                      '[JSON]
                                                                                                      NewTeamMember
                                                                                                    :> MultiVerb
                                                                                                         'PUT
                                                                                                         '[JSON]
                                                                                                         '[RespondEmpty
                                                                                                             200
                                                                                                             ""]
                                                                                                         ())))))))))))))
                                         :<|> (Named
                                                 "user-is-team-owner"
                                                 ("is-team-owner"
                                                  :> (Capture "uid" UserId
                                                      :> (CanThrow 'AccessDenied
                                                          :> (CanThrow 'TeamMemberNotFound
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> MultiVerb
                                                                       'GET
                                                                       '[JSON]
                                                                       '[RespondEmpty
                                                                           200 "User is team owner"]
                                                                       ())))))
                                               :<|> ("search-visibility"
                                                     :> (Named
                                                           "get-search-visibility-internal"
                                                           (Get '[JSON] TeamSearchVisibilityView)
                                                         :<|> Named
                                                                "set-search-visibility-internal"
                                                                (CanThrow
                                                                   'TeamSearchVisibilityNotEnabled
                                                                 :> (CanThrow
                                                                       ('MissingPermission 'Nothing)
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   TeamSearchVisibilityView
                                                                                 :> MultiVerb
                                                                                      'PUT
                                                                                      '[JSON]
                                                                                      '[RespondEmpty
                                                                                          204 "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 ITeamsAPI GalleyEffects
iTeamsAPI
      API
  ("teams"
   :> (Capture "tid" TeamId
       :> (Named
             "get-team-internal"
             (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
           :<|> (Named
                   "create-binding-team"
                   (ZUser
                    :> (ReqBody '[JSON] BindingNewTeam
                        :> MultiVerb
                             'PUT
                             '[JSON]
                             '[WithHeaders
                                 '[Header "Location" TeamId] TeamId (RespondEmpty 201 "OK")]
                             TeamId))
                 :<|> (Named
                         "delete-binding-team"
                         (CanThrow 'NoBindingTeam
                          :> (CanThrow 'NotAOneMemberTeam
                              :> (CanThrow 'DeleteQueueFull
                                  :> (CanThrow 'TeamNotFound
                                      :> (QueryFlag "force"
                                          :> MultiVerb
                                               'DELETE '[JSON] '[RespondEmpty 202 "OK"] ())))))
                       :<|> (Named
                               "get-team-name"
                               ("name" :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
                             :<|> (Named
                                     "update-team-status"
                                     ("status"
                                      :> (CanThrow 'TeamNotFound
                                          :> (CanThrow 'InvalidTeamStatusUpdate
                                              :> (ReqBody '[JSON] TeamStatusUpdate
                                                  :> MultiVerb
                                                       'PUT '[JSON] '[RespondEmpty 200 "OK"] ()))))
                                   :<|> (("members"
                                          :> (Named
                                                "unchecked-add-team-member"
                                                (CanThrow 'TooManyTeamMembers
                                                 :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                                     :> (CanThrow 'TooManyTeamAdmins
                                                         :> (ReqBody '[JSON] NewTeamMember
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[RespondEmpty 200 "OK"]
                                                                  ()))))
                                              :<|> (Named
                                                      "unchecked-get-team-members"
                                                      (QueryParam'
                                                         '[Strict]
                                                         "maxResults"
                                                         (Range 1 HardTruncationLimit Int32)
                                                       :> Get '[JSON] TeamMemberList)
                                                    :<|> (Named
                                                            "unchecked-get-team-member"
                                                            (Capture "uid" UserId
                                                             :> (CanThrow 'TeamMemberNotFound
                                                                 :> Get '[JSON] TeamMember))
                                                          :<|> (Named
                                                                  "can-user-join-team"
                                                                  ("check"
                                                                   :> (CanThrow
                                                                         'TooManyTeamMembersOnTeamWithLegalhold
                                                                       :> MultiVerb
                                                                            'GET
                                                                            '[JSON]
                                                                            '[RespondEmpty
                                                                                200 "User can join"]
                                                                            ()))
                                                                :<|> Named
                                                                       "unchecked-update-team-member"
                                                                       (CanThrow 'AccessDenied
                                                                        :> (CanThrow
                                                                              'InvalidPermissions
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      'TeamMemberNotFound
                                                                                    :> (CanThrow
                                                                                          'TooManyTeamAdmins
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (ReqBody
                                                                                                      '[JSON]
                                                                                                      NewTeamMember
                                                                                                    :> MultiVerb
                                                                                                         'PUT
                                                                                                         '[JSON]
                                                                                                         '[RespondEmpty
                                                                                                             200
                                                                                                             ""]
                                                                                                         ())))))))))))))
                                         :<|> (Named
                                                 "user-is-team-owner"
                                                 ("is-team-owner"
                                                  :> (Capture "uid" UserId
                                                      :> (CanThrow 'AccessDenied
                                                          :> (CanThrow 'TeamMemberNotFound
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> MultiVerb
                                                                       'GET
                                                                       '[JSON]
                                                                       '[RespondEmpty
                                                                           200 "User is team owner"]
                                                                       ())))))
                                               :<|> ("search-visibility"
                                                     :> (Named
                                                           "get-search-visibility-internal"
                                                           (Get '[JSON] TeamSearchVisibilityView)
                                                         :<|> Named
                                                                "set-search-visibility-internal"
                                                                (CanThrow
                                                                   'TeamSearchVisibilityNotEnabled
                                                                 :> (CanThrow
                                                                       ('MissingPermission 'Nothing)
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   TeamSearchVisibilityView
                                                                                 :> MultiVerb
                                                                                      'PUT
                                                                                      '[JSON]
                                                                                      '[RespondEmpty
                                                                                          204 "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
         "get-team-members"
         (CanThrow 'NonBindingTeam
          :> (CanThrow 'TeamNotFound
              :> ("users"
                  :> (Capture "uid" UserId
                      :> ("team" :> ("members" :> Get '[JSON] TeamMemberList))))))
       :<|> (Named
               "get-team-id"
               (CanThrow 'NonBindingTeam
                :> (CanThrow 'TeamNotFound
                    :> ("users"
                        :> (Capture "uid" UserId :> ("team" :> Get '[JSON] TeamId)))))
             :<|> (Named
                     "test-get-clients"
                     ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
                   :<|> (Named
                           "test-add-client"
                           ("clients"
                            :> (ZUser
                                :> (Capture "cid" ClientId
                                    :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
                         :<|> (Named
                                 "test-delete-client"
                                 ("clients"
                                  :> (ZUser
                                      :> (Capture "cid" ClientId
                                          :> MultiVerb
                                               'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
                               :<|> (Named
                                       "add-service"
                                       ("services"
                                        :> (ReqBody '[JSON] Service
                                            :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
                                     :<|> (Named
                                             "delete-service"
                                             ("services"
                                              :> (ReqBody '[JSON] ServiceRef
                                                  :> MultiVerb
                                                       'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
                                           :<|> (Named
                                                   "i-add-bot"
                                                   (CanThrow ('ActionDenied 'AddConversationMember)
                                                    :> (CanThrow 'ConvNotFound
                                                        :> (CanThrow 'InvalidOperation
                                                            :> (CanThrow 'TooManyMembers
                                                                :> ("bots"
                                                                    :> (ZLocalUser
                                                                        :> (ZConn
                                                                            :> (ReqBody
                                                                                  '[JSON] AddBot
                                                                                :> Post
                                                                                     '[JSON]
                                                                                     Event))))))))
                                                 :<|> (Named
                                                         "delete-bot"
                                                         (CanThrow 'ConvNotFound
                                                          :> (CanThrow
                                                                ('ActionDenied
                                                                   'RemoveConversationMember)
                                                              :> ("bots"
                                                                  :> (ZLocalUser
                                                                      :> (ZOptConn
                                                                          :> (ReqBody
                                                                                '[JSON] RemoveBot
                                                                              :> MultiVerb
                                                                                   'DELETE
                                                                                   '[JSON]
                                                                                   (UpdateResponses
                                                                                      "Bot not found"
                                                                                      "Bot deleted"
                                                                                      Event)
                                                                                   (UpdateResult
                                                                                      Event)))))))
                                                       :<|> (Named
                                                               "put-custom-backend"
                                                               ("custom-backend"
                                                                :> ("by-domain"
                                                                    :> (Capture "domain" Domain
                                                                        :> (ReqBody
                                                                              '[JSON] CustomBackend
                                                                            :> MultiVerb
                                                                                 'PUT
                                                                                 '[JSON]
                                                                                 '[RespondEmpty
                                                                                     201 "OK"]
                                                                                 ()))))
                                                             :<|> Named
                                                                    "delete-custom-backend"
                                                                    ("custom-backend"
                                                                     :> ("by-domain"
                                                                         :> (Capture "domain" Domain
                                                                             :> MultiVerb
                                                                                  'DELETE
                                                                                  '[JSON]
                                                                                  '[RespondEmpty
                                                                                      200 "OK"]
                                                                                  ())))))))))))))
      :<|> (Named
              "upsert-one2one"
              (Summary "Create or Update a connect or one2one conversation."
               :> ("conversations"
                   :> ("one2one"
                       :> ("upsert"
                           :> (ReqBody '[JSON] UpsertOne2OneConversationRequest
                               :> MultiVerb
                                    'POST
                                    '[JSON]
                                    '[RespondEmpty 200 "Upsert One2One Policy"]
                                    ())))))
            :<|> ((((Named
                       '("iget", LegalholdConfig)
                       (Description ""
                        :> (Summary "Get config for legalhold"
                            :> (CanThrow ('MissingPermission 'Nothing)
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("legalhold"
                                                        :> Get
                                                             '[JSON]
                                                             (LockableFeature
                                                                LegalholdConfig))))))))))
                     :<|> (Named
                             '("iput", LegalholdConfig)
                             (Description ""
                              :> (Summary "Put config for legalhold"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> (CanThrow TeamFeatureError
                                                  :> (CanThrowMany
                                                        '[ 'ActionDenied 'RemoveConversationMember,
                                                           'CannotEnableLegalHoldServiceLargeTeam,
                                                           'LegalHoldNotEnabled,
                                                           'LegalHoldDisableUnimplemented,
                                                           'LegalHoldServiceNotRegistered,
                                                           'UserLegalHoldIllegalOperation,
                                                           'LegalHoldCouldNotBlockConnections]
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("legalhold"
                                                                      :> (ReqBody
                                                                            '[JSON]
                                                                            (Feature
                                                                               LegalholdConfig)
                                                                          :> Put
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  LegalholdConfig)))))))))))))
                           :<|> Named
                                  '("ipatch", LegalholdConfig)
                                  (Description ""
                                   :> (Summary "Patch config for legalhold"
                                       :> (CanThrow ('MissingPermission 'Nothing)
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany
                                                             '[ 'ActionDenied
                                                                  'RemoveConversationMember,
                                                                'CannotEnableLegalHoldServiceLargeTeam,
                                                                'LegalHoldNotEnabled,
                                                                'LegalHoldDisableUnimplemented,
                                                                'LegalHoldServiceNotRegistered,
                                                                'UserLegalHoldIllegalOperation,
                                                                'LegalHoldCouldNotBlockConnections]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("legalhold"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (LockableFeaturePatch
                                                                                    LegalholdConfig)
                                                                               :> Patch
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       LegalholdConfig)))))))))))))))
                    :<|> ((Named
                             '("iget", SSOConfig)
                             (Description ""
                              :> (Summary "Get config for sso"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("sso"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      SSOConfig))))))))))
                           :<|> (Named
                                   '("iput", SSOConfig)
                                   (Description ""
                                    :> (Summary "Put config for sso"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> (CanThrow TeamFeatureError
                                                        :> (CanThrowMany '[]
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("sso"
                                                                            :> (ReqBody
                                                                                  '[JSON]
                                                                                  (Feature
                                                                                     SSOConfig)
                                                                                :> Put
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SSOConfig)))))))))))))
                                 :<|> Named
                                        '("ipatch", SSOConfig)
                                        (Description ""
                                         :> (Summary "Patch config for sso"
                                             :> (CanThrow ('MissingPermission 'Nothing)
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("sso"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (LockableFeaturePatch
                                                                                          SSOConfig)
                                                                                     :> Patch
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             SSOConfig)))))))))))))))
                          :<|> ((Named
                                   '("iget", SearchVisibilityAvailableConfig)
                                   (Description ""
                                    :> (Summary "Get config for searchVisibility"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("searchVisibility"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            SearchVisibilityAvailableConfig))))))))))
                                 :<|> (Named
                                         '("iput", SearchVisibilityAvailableConfig)
                                         (Description ""
                                          :> (Summary "Put config for searchVisibility"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow TeamFeatureError
                                                              :> (CanThrowMany '[]
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("searchVisibility"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        (Feature
                                                                                           SearchVisibilityAvailableConfig)
                                                                                      :> Put
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              SearchVisibilityAvailableConfig)))))))))))))
                                       :<|> Named
                                              '("ipatch", SearchVisibilityAvailableConfig)
                                              (Description ""
                                               :> (Summary "Patch config for searchVisibility"
                                                   :> (CanThrow ('MissingPermission 'Nothing)
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("searchVisibility"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (LockableFeaturePatch
                                                                                                SearchVisibilityAvailableConfig)
                                                                                           :> Patch
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   SearchVisibilityAvailableConfig)))))))))))))))
                                :<|> ((Named
                                         '("iget", SearchVisibilityInboundConfig)
                                         (Description ""
                                          :> (Summary "Get config for searchVisibilityInbound"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("searchVisibilityInbound"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  SearchVisibilityInboundConfig))))))))))
                                       :<|> (Named
                                               '("iput", SearchVisibilityInboundConfig)
                                               (Description ""
                                                :> (Summary "Put config for searchVisibilityInbound"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> (CanThrowMany '[]
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("searchVisibilityInbound"
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              (Feature
                                                                                                 SearchVisibilityInboundConfig)
                                                                                            :> Put
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    SearchVisibilityInboundConfig)))))))))))))
                                             :<|> Named
                                                    '("ipatch", SearchVisibilityInboundConfig)
                                                    (Description ""
                                                     :> (Summary
                                                           "Patch config for searchVisibilityInbound"
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("searchVisibilityInbound"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (LockableFeaturePatch
                                                                                                      SearchVisibilityInboundConfig)
                                                                                                 :> Patch
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         SearchVisibilityInboundConfig)))))))))))))))
                                      :<|> ((Named
                                               '("iget", ValidateSAMLEmailsConfig)
                                               (Description ""
                                                :> (Summary "Get config for validateSAMLemails"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("validateSAMLemails"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        ValidateSAMLEmailsConfig))))))))))
                                             :<|> (Named
                                                     '("iput", ValidateSAMLEmailsConfig)
                                                     (Description ""
                                                      :> (Summary
                                                            "Put config for validateSAMLemails"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany '[]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("validateSAMLemails"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (Feature
                                                                                                       ValidateSAMLEmailsConfig)
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          ValidateSAMLEmailsConfig)))))))))))))
                                                   :<|> Named
                                                          '("ipatch", ValidateSAMLEmailsConfig)
                                                          (Description ""
                                                           :> (Summary
                                                                 "Patch config for validateSAMLemails"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("validateSAMLemails"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (LockableFeaturePatch
                                                                                                            ValidateSAMLEmailsConfig)
                                                                                                       :> Patch
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               ValidateSAMLEmailsConfig)))))))))))))))
                                            :<|> ((Named
                                                     '("iget", DigitalSignaturesConfig)
                                                     (Description ""
                                                      :> (Summary "Get config for digitalSignatures"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("digitalSignatures"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              DigitalSignaturesConfig))))))))))
                                                   :<|> (Named
                                                           '("iput", DigitalSignaturesConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Put config for digitalSignatures"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("digitalSignatures"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             DigitalSignaturesConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                DigitalSignaturesConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch", DigitalSignaturesConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Patch config for digitalSignatures"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("digitalSignatures"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  DigitalSignaturesConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     DigitalSignaturesConfig)))))))))))))))
                                                  :<|> ((Named
                                                           '("iget", AppLockConfig)
                                                           (Description ""
                                                            :> (Summary "Get config for appLock"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("appLock"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    AppLockConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput", AppLockConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Put config for appLock"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("appLock"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   AppLockConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      AppLockConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch", AppLockConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for appLock"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("appLock"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        AppLockConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           AppLockConfig)))))))))))))))
                                                        :<|> ((Named
                                                                 '("iget", FileSharingConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Get config for fileSharing"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("fileSharing"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          FileSharingConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput", FileSharingConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for fileSharing"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("fileSharing"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         FileSharingConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            FileSharingConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch",
                                                                              FileSharingConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for fileSharing"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("fileSharing"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              FileSharingConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 FileSharingConfig)))))))))))))))
                                                              :<|> (Named
                                                                      '("iget",
                                                                        ClassifiedDomainsConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Get config for classifiedDomains"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("classifiedDomains"
                                                                                                       :> Get
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               ClassifiedDomainsConfig))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               ConferenceCallingConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for conferenceCalling"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("conferenceCalling"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      ConferenceCallingConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     ConferenceCallingConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for conferenceCalling"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("conferenceCalling"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     ConferenceCallingConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        ConferenceCallingConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          ConferenceCallingConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for conferenceCalling"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("conferenceCalling"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          ConferenceCallingConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             ConferenceCallingConfig)))))))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     SelfDeletingMessagesConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for selfDeletingMessages"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("selfDeletingMessages"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            SelfDeletingMessagesConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           SelfDeletingMessagesConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for selfDeletingMessages"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("selfDeletingMessages"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           SelfDeletingMessagesConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              SelfDeletingMessagesConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                SelfDeletingMessagesConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for selfDeletingMessages"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("selfDeletingMessages"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                SelfDeletingMessagesConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   SelfDeletingMessagesConfig)))))))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           GuestLinksConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for conversationGuestLinks"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("conversationGuestLinks"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  GuestLinksConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 GuestLinksConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for conversationGuestLinks"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("conversationGuestLinks"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 GuestLinksConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    GuestLinksConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      GuestLinksConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for conversationGuestLinks"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      GuestLinksConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         GuestLinksConfig)))))))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 SndFactorPasswordChallengeConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for sndFactorPasswordChallenge"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("sndFactorPasswordChallenge"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        SndFactorPasswordChallengeConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       SndFactorPasswordChallengeConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for sndFactorPasswordChallenge"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("sndFactorPasswordChallenge"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       SndFactorPasswordChallengeConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          SndFactorPasswordChallengeConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for sndFactorPasswordChallenge"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("sndFactorPasswordChallenge"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       MLSConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for mls"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("mls"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              MLSConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             MLSConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for mls"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("mls"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             MLSConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                MLSConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  MLSConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for mls"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("mls"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  MLSConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     MLSConfig)))))))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   OutlookCalIntegrationConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for outlookCalIntegration"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("outlookCalIntegration"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          OutlookCalIntegrationConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         OutlookCalIntegrationConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for outlookCalIntegration"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("outlookCalIntegration"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         OutlookCalIntegrationConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            OutlookCalIntegrationConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              OutlookCalIntegrationConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for outlookCalIntegration"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("outlookCalIntegration"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              OutlookCalIntegrationConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 OutlookCalIntegrationConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         MlsE2EIdConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for mlsE2EId"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("mlsE2EId"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                MlsE2EIdConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               MlsE2EIdConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for mlsE2EId"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("mlsE2EId"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               MlsE2EIdConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  MlsE2EIdConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    MlsE2EIdConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for mlsE2EId"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("mlsE2EId"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    MlsE2EIdConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       MlsE2EIdConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               MlsMigrationConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for mlsMigration"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("mlsMigration"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      MlsMigrationConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     MlsMigrationConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for mlsMigration"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("mlsMigration"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     MlsMigrationConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        MlsMigrationConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          MlsMigrationConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for mlsMigration"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("mlsMigration"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          MlsMigrationConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             MlsMigrationConfig)))))))))))))))
                                                                                                                          :<|> ((Named
                                                                                                                                   '("iget",
                                                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                                                   (Description
                                                                                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for enforceFileDownloadLocation"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                 :<|> (Named
                                                                                                                                         '("iput",
                                                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                                                         (Description
                                                                                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                          :> (Summary
                                                                                                                                                "Put config for enforceFileDownloadLocation"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Feature
                                                                                                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                                                                                                      :> Put
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                       :<|> Named
                                                                                                                                              '("ipatch",
                                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                                              (Description
                                                                                                                                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                               :> (Summary
                                                                                                                                                     "Patch config for enforceFileDownloadLocation"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("enforceFileDownloadLocation"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                :<|> (Named
                                                                                                                                        '("iget",
                                                                                                                                          LimitedEventFanoutConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Get config for limitedEventFanout"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("teams"
                                                                                                                                                             :> (Capture
                                                                                                                                                                   "tid"
                                                                                                                                                                   TeamId
                                                                                                                                                                 :> ("features"
                                                                                                                                                                     :> ("limitedEventFanout"
                                                                                                                                                                         :> Get
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 LimitedEventFanoutConfig))))))))))
                                                                                                                                      :<|> (Named
                                                                                                                                              '("iput",
                                                                                                                                                LimitedEventFanoutConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Put config for limitedEventFanout"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("limitedEventFanout"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (Feature
                                                                                                                                                                                                LimitedEventFanoutConfig)
                                                                                                                                                                                           :> Put
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   LimitedEventFanoutConfig)))))))))))))
                                                                                                                                            :<|> Named
                                                                                                                                                   '("ipatch",
                                                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                                                   (Description
                                                                                                                                                      ""
                                                                                                                                                    :> (Summary
                                                                                                                                                          "Patch config for limitedEventFanout"
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              ('MissingPermission
                                                                                                                                                                 'Nothing)
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          TeamFeatureError
                                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                                              '[]
                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                :> (Capture
                                                                                                                                                                                      "tid"
                                                                                                                                                                                      TeamId
                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                        :> ("limitedEventFanout"
                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  (LockableFeaturePatch
                                                                                                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                                                                                                :> Patch
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                                        LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                   :<|> (Named
                           '("ilock", FileSharingConfig)
                           (Summary "(Un-)lock fileSharing"
                            :> (Description ""
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("fileSharing"
                                                        :> (Capture "lockStatus" LockStatus
                                                            :> Put
                                                                 '[JSON] LockStatusResponse)))))))))
                         :<|> (Named
                                 '("ilock", ConferenceCallingConfig)
                                 (Summary "(Un-)lock conferenceCalling"
                                  :> (Description ""
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("conferenceCalling"
                                                              :> (Capture "lockStatus" LockStatus
                                                                  :> Put
                                                                       '[JSON]
                                                                       LockStatusResponse)))))))))
                               :<|> (Named
                                       '("ilock", SelfDeletingMessagesConfig)
                                       (Summary "(Un-)lock selfDeletingMessages"
                                        :> (Description ""
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("selfDeletingMessages"
                                                                    :> (Capture
                                                                          "lockStatus" LockStatus
                                                                        :> Put
                                                                             '[JSON]
                                                                             LockStatusResponse)))))))))
                                     :<|> (Named
                                             '("ilock", GuestLinksConfig)
                                             (Summary "(Un-)lock conversationGuestLinks"
                                              :> (Description ""
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("conversationGuestLinks"
                                                                          :> (Capture
                                                                                "lockStatus"
                                                                                LockStatus
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   LockStatusResponse)))))))))
                                           :<|> (Named
                                                   '("ilock", SndFactorPasswordChallengeConfig)
                                                   (Summary "(Un-)lock sndFactorPasswordChallenge"
                                                    :> (Description ""
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("sndFactorPasswordChallenge"
                                                                                :> (Capture
                                                                                      "lockStatus"
                                                                                      LockStatus
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         LockStatusResponse)))))))))
                                                 :<|> (Named
                                                         '("ilock", MLSConfig)
                                                         (Summary "(Un-)lock mls"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("mls"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock",
                                                                 OutlookCalIntegrationConfig)
                                                               (Summary
                                                                  "(Un-)lock outlookCalIntegration"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("outlookCalIntegration"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock", MlsE2EIdConfig)
                                                                     (Summary "(Un-)lock mlsE2EId"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mlsE2EId"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock",
                                                                             MlsMigrationConfig)
                                                                           (Summary
                                                                              "(Un-)lock mlsMigration"
                                                                            :> (Description ""
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mlsMigration"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("ilock",
                                                                                   EnforceFileDownloadLocationConfig)
                                                                                 (Summary
                                                                                    "(Un-)lock enforceFileDownloadLocation"
                                                                                  :> (Description
                                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                              :> (Capture
                                                                                                                    "lockStatus"
                                                                                                                    LockStatus
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       LockStatusResponse)))))))))
                                                                               :<|> (Named
                                                                                       '("igetmulti",
                                                                                         SearchVisibilityInboundConfig)
                                                                                       (Summary
                                                                                          "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                        :> ("features-multi-teams"
                                                                                            :> ("searchVisibilityInbound"
                                                                                                :> (ReqBody
                                                                                                      '[JSON]
                                                                                                      TeamFeatureNoConfigMultiRequest
                                                                                                    :> Post
                                                                                                         '[JSON]
                                                                                                         (TeamFeatureNoConfigMultiResponse
                                                                                                            SearchVisibilityInboundConfig)))))
                                                                                     :<|> Named
                                                                                            "feature-configs-internal"
                                                                                            (Summary
                                                                                               "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                             :> ("feature-configs"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (QueryParam'
                                                                                                                   '[Optional,
                                                                                                                     Strict,
                                                                                                                     Description
                                                                                                                       "Optional user id"]
                                                                                                                   "user_id"
                                                                                                                   UserId
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      AllTeamFeatures))))))))))))))))))
                  :<|> (IFederationAPI :<|> (IConversationAPI :<|> IEJPDAPI)))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
     (("teams"
       :> (Capture "tid" TeamId
           :> (Named
                 "get-team-internal"
                 (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
               :<|> (Named
                       "create-binding-team"
                       (ZUser
                        :> (ReqBody '[JSON] BindingNewTeam
                            :> MultiVerb
                                 'PUT
                                 '[JSON]
                                 '[WithHeaders
                                     '[Header "Location" TeamId] TeamId (RespondEmpty 201 "OK")]
                                 TeamId))
                     :<|> (Named
                             "delete-binding-team"
                             (CanThrow 'NoBindingTeam
                              :> (CanThrow 'NotAOneMemberTeam
                                  :> (CanThrow 'DeleteQueueFull
                                      :> (CanThrow 'TeamNotFound
                                          :> (QueryFlag "force"
                                              :> MultiVerb
                                                   'DELETE '[JSON] '[RespondEmpty 202 "OK"] ())))))
                           :<|> (Named
                                   "get-team-name"
                                   ("name" :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
                                 :<|> (Named
                                         "update-team-status"
                                         ("status"
                                          :> (CanThrow 'TeamNotFound
                                              :> (CanThrow 'InvalidTeamStatusUpdate
                                                  :> (ReqBody '[JSON] TeamStatusUpdate
                                                      :> MultiVerb
                                                           'PUT
                                                           '[JSON]
                                                           '[RespondEmpty 200 "OK"]
                                                           ()))))
                                       :<|> (("members"
                                              :> (Named
                                                    "unchecked-add-team-member"
                                                    (CanThrow 'TooManyTeamMembers
                                                     :> (CanThrow
                                                           'TooManyTeamMembersOnTeamWithLegalhold
                                                         :> (CanThrow 'TooManyTeamAdmins
                                                             :> (ReqBody '[JSON] NewTeamMember
                                                                 :> MultiVerb
                                                                      'POST
                                                                      '[JSON]
                                                                      '[RespondEmpty 200 "OK"]
                                                                      ()))))
                                                  :<|> (Named
                                                          "unchecked-get-team-members"
                                                          (QueryParam'
                                                             '[Strict]
                                                             "maxResults"
                                                             (Range 1 HardTruncationLimit Int32)
                                                           :> Get '[JSON] TeamMemberList)
                                                        :<|> (Named
                                                                "unchecked-get-team-member"
                                                                (Capture "uid" UserId
                                                                 :> (CanThrow 'TeamMemberNotFound
                                                                     :> Get '[JSON] TeamMember))
                                                              :<|> (Named
                                                                      "can-user-join-team"
                                                                      ("check"
                                                                       :> (CanThrow
                                                                             'TooManyTeamMembersOnTeamWithLegalhold
                                                                           :> MultiVerb
                                                                                'GET
                                                                                '[JSON]
                                                                                '[RespondEmpty
                                                                                    200
                                                                                    "User can join"]
                                                                                ()))
                                                                    :<|> Named
                                                                           "unchecked-update-team-member"
                                                                           (CanThrow 'AccessDenied
                                                                            :> (CanThrow
                                                                                  'InvalidPermissions
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> (CanThrow
                                                                                          'TeamMemberNotFound
                                                                                        :> (CanThrow
                                                                                              'TooManyTeamAdmins
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      ('MissingPermission
                                                                                                         'Nothing)
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          NewTeamMember
                                                                                                        :> MultiVerb
                                                                                                             'PUT
                                                                                                             '[JSON]
                                                                                                             '[RespondEmpty
                                                                                                                 200
                                                                                                                 ""]
                                                                                                             ())))))))))))))
                                             :<|> (Named
                                                     "user-is-team-owner"
                                                     ("is-team-owner"
                                                      :> (Capture "uid" UserId
                                                          :> (CanThrow 'AccessDenied
                                                              :> (CanThrow 'TeamMemberNotFound
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> MultiVerb
                                                                           'GET
                                                                           '[JSON]
                                                                           '[RespondEmpty
                                                                               200
                                                                               "User is team owner"]
                                                                           ())))))
                                                   :<|> ("search-visibility"
                                                         :> (Named
                                                               "get-search-visibility-internal"
                                                               (Get
                                                                  '[JSON] TeamSearchVisibilityView)
                                                             :<|> Named
                                                                    "set-search-visibility-internal"
                                                                    (CanThrow
                                                                       'TeamSearchVisibilityNotEnabled
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       TeamSearchVisibilityView
                                                                                     :> MultiVerb
                                                                                          'PUT
                                                                                          '[JSON]
                                                                                          '[RespondEmpty
                                                                                              204
                                                                                              "OK"]
                                                                                          ()))))))))))))))))
      :<|> ((Named
               "get-team-members"
               (CanThrow 'NonBindingTeam
                :> (CanThrow 'TeamNotFound
                    :> ("users"
                        :> (Capture "uid" UserId
                            :> ("team" :> ("members" :> Get '[JSON] TeamMemberList))))))
             :<|> (Named
                     "get-team-id"
                     (CanThrow 'NonBindingTeam
                      :> (CanThrow 'TeamNotFound
                          :> ("users"
                              :> (Capture "uid" UserId :> ("team" :> Get '[JSON] TeamId)))))
                   :<|> (Named
                           "test-get-clients"
                           ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
                         :<|> (Named
                                 "test-add-client"
                                 ("clients"
                                  :> (ZUser
                                      :> (Capture "cid" ClientId
                                          :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
                               :<|> (Named
                                       "test-delete-client"
                                       ("clients"
                                        :> (ZUser
                                            :> (Capture "cid" ClientId
                                                :> MultiVerb
                                                     'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
                                     :<|> (Named
                                             "add-service"
                                             ("services"
                                              :> (ReqBody '[JSON] Service
                                                  :> MultiVerb
                                                       'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
                                           :<|> (Named
                                                   "delete-service"
                                                   ("services"
                                                    :> (ReqBody '[JSON] ServiceRef
                                                        :> MultiVerb
                                                             'DELETE
                                                             '[JSON]
                                                             '[RespondEmpty 200 "OK"]
                                                             ()))
                                                 :<|> (Named
                                                         "i-add-bot"
                                                         (CanThrow
                                                            ('ActionDenied 'AddConversationMember)
                                                          :> (CanThrow 'ConvNotFound
                                                              :> (CanThrow 'InvalidOperation
                                                                  :> (CanThrow 'TooManyMembers
                                                                      :> ("bots"
                                                                          :> (ZLocalUser
                                                                              :> (ZConn
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        AddBot
                                                                                      :> Post
                                                                                           '[JSON]
                                                                                           Event))))))))
                                                       :<|> (Named
                                                               "delete-bot"
                                                               (CanThrow 'ConvNotFound
                                                                :> (CanThrow
                                                                      ('ActionDenied
                                                                         'RemoveConversationMember)
                                                                    :> ("bots"
                                                                        :> (ZLocalUser
                                                                            :> (ZOptConn
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      RemoveBot
                                                                                    :> MultiVerb
                                                                                         'DELETE
                                                                                         '[JSON]
                                                                                         (UpdateResponses
                                                                                            "Bot not found"
                                                                                            "Bot deleted"
                                                                                            Event)
                                                                                         (UpdateResult
                                                                                            Event)))))))
                                                             :<|> (Named
                                                                     "put-custom-backend"
                                                                     ("custom-backend"
                                                                      :> ("by-domain"
                                                                          :> (Capture
                                                                                "domain" Domain
                                                                              :> (ReqBody
                                                                                    '[JSON]
                                                                                    CustomBackend
                                                                                  :> MultiVerb
                                                                                       'PUT
                                                                                       '[JSON]
                                                                                       '[RespondEmpty
                                                                                           201 "OK"]
                                                                                       ()))))
                                                                   :<|> Named
                                                                          "delete-custom-backend"
                                                                          ("custom-backend"
                                                                           :> ("by-domain"
                                                                               :> (Capture
                                                                                     "domain" Domain
                                                                                   :> MultiVerb
                                                                                        'DELETE
                                                                                        '[JSON]
                                                                                        '[RespondEmpty
                                                                                            200
                                                                                            "OK"]
                                                                                        ())))))))))))))
            :<|> (Named
                    "upsert-one2one"
                    (Summary "Create or Update a connect or one2one conversation."
                     :> ("conversations"
                         :> ("one2one"
                             :> ("upsert"
                                 :> (ReqBody '[JSON] UpsertOne2OneConversationRequest
                                     :> MultiVerb
                                          'POST
                                          '[JSON]
                                          '[RespondEmpty 200 "Upsert One2One Policy"]
                                          ())))))
                  :<|> ((((Named
                             '("iget", LegalholdConfig)
                             (Description ""
                              :> (Summary "Get config for legalhold"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("legalhold"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      LegalholdConfig))))))))))
                           :<|> (Named
                                   '("iput", LegalholdConfig)
                                   (Description ""
                                    :> (Summary "Put config for legalhold"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> (CanThrow TeamFeatureError
                                                        :> (CanThrowMany
                                                              '[ 'ActionDenied
                                                                   'RemoveConversationMember,
                                                                 'CannotEnableLegalHoldServiceLargeTeam,
                                                                 'LegalHoldNotEnabled,
                                                                 'LegalHoldDisableUnimplemented,
                                                                 'LegalHoldServiceNotRegistered,
                                                                 'UserLegalHoldIllegalOperation,
                                                                 'LegalHoldCouldNotBlockConnections]
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("legalhold"
                                                                            :> (ReqBody
                                                                                  '[JSON]
                                                                                  (Feature
                                                                                     LegalholdConfig)
                                                                                :> Put
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        LegalholdConfig)))))))))))))
                                 :<|> Named
                                        '("ipatch", LegalholdConfig)
                                        (Description ""
                                         :> (Summary "Patch config for legalhold"
                                             :> (CanThrow ('MissingPermission 'Nothing)
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany
                                                                   '[ 'ActionDenied
                                                                        'RemoveConversationMember,
                                                                      'CannotEnableLegalHoldServiceLargeTeam,
                                                                      'LegalHoldNotEnabled,
                                                                      'LegalHoldDisableUnimplemented,
                                                                      'LegalHoldServiceNotRegistered,
                                                                      'UserLegalHoldIllegalOperation,
                                                                      'LegalHoldCouldNotBlockConnections]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("legalhold"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (LockableFeaturePatch
                                                                                          LegalholdConfig)
                                                                                     :> Patch
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             LegalholdConfig)))))))))))))))
                          :<|> ((Named
                                   '("iget", SSOConfig)
                                   (Description ""
                                    :> (Summary "Get config for sso"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("sso"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            SSOConfig))))))))))
                                 :<|> (Named
                                         '("iput", SSOConfig)
                                         (Description ""
                                          :> (Summary "Put config for sso"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow TeamFeatureError
                                                              :> (CanThrowMany '[]
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("sso"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        (Feature
                                                                                           SSOConfig)
                                                                                      :> Put
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              SSOConfig)))))))))))))
                                       :<|> Named
                                              '("ipatch", SSOConfig)
                                              (Description ""
                                               :> (Summary "Patch config for sso"
                                                   :> (CanThrow ('MissingPermission 'Nothing)
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("sso"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (LockableFeaturePatch
                                                                                                SSOConfig)
                                                                                           :> Patch
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   SSOConfig)))))))))))))))
                                :<|> ((Named
                                         '("iget", SearchVisibilityAvailableConfig)
                                         (Description ""
                                          :> (Summary "Get config for searchVisibility"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("searchVisibility"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  SearchVisibilityAvailableConfig))))))))))
                                       :<|> (Named
                                               '("iput", SearchVisibilityAvailableConfig)
                                               (Description ""
                                                :> (Summary "Put config for searchVisibility"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> (CanThrowMany '[]
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("searchVisibility"
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              (Feature
                                                                                                 SearchVisibilityAvailableConfig)
                                                                                            :> Put
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    SearchVisibilityAvailableConfig)))))))))))))
                                             :<|> Named
                                                    '("ipatch", SearchVisibilityAvailableConfig)
                                                    (Description ""
                                                     :> (Summary "Patch config for searchVisibility"
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("searchVisibility"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (LockableFeaturePatch
                                                                                                      SearchVisibilityAvailableConfig)
                                                                                                 :> Patch
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         SearchVisibilityAvailableConfig)))))))))))))))
                                      :<|> ((Named
                                               '("iget", SearchVisibilityInboundConfig)
                                               (Description ""
                                                :> (Summary "Get config for searchVisibilityInbound"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("searchVisibilityInbound"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SearchVisibilityInboundConfig))))))))))
                                             :<|> (Named
                                                     '("iput", SearchVisibilityInboundConfig)
                                                     (Description ""
                                                      :> (Summary
                                                            "Put config for searchVisibilityInbound"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany '[]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("searchVisibilityInbound"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (Feature
                                                                                                       SearchVisibilityInboundConfig)
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          SearchVisibilityInboundConfig)))))))))))))
                                                   :<|> Named
                                                          '("ipatch", SearchVisibilityInboundConfig)
                                                          (Description ""
                                                           :> (Summary
                                                                 "Patch config for searchVisibilityInbound"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("searchVisibilityInbound"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (LockableFeaturePatch
                                                                                                            SearchVisibilityInboundConfig)
                                                                                                       :> Patch
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               SearchVisibilityInboundConfig)))))))))))))))
                                            :<|> ((Named
                                                     '("iget", ValidateSAMLEmailsConfig)
                                                     (Description ""
                                                      :> (Summary
                                                            "Get config for validateSAMLemails"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("validateSAMLemails"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              ValidateSAMLEmailsConfig))))))))))
                                                   :<|> (Named
                                                           '("iput", ValidateSAMLEmailsConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Put config for validateSAMLemails"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("validateSAMLemails"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             ValidateSAMLEmailsConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                ValidateSAMLEmailsConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch",
                                                                  ValidateSAMLEmailsConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Patch config for validateSAMLemails"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("validateSAMLemails"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  ValidateSAMLEmailsConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     ValidateSAMLEmailsConfig)))))))))))))))
                                                  :<|> ((Named
                                                           '("iget", DigitalSignaturesConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Get config for digitalSignatures"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("digitalSignatures"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    DigitalSignaturesConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput", DigitalSignaturesConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Put config for digitalSignatures"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("digitalSignatures"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   DigitalSignaturesConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      DigitalSignaturesConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch",
                                                                        DigitalSignaturesConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for digitalSignatures"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("digitalSignatures"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        DigitalSignaturesConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           DigitalSignaturesConfig)))))))))))))))
                                                        :<|> ((Named
                                                                 '("iget", AppLockConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Get config for appLock"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("appLock"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          AppLockConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput", AppLockConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for appLock"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("appLock"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         AppLockConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            AppLockConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch",
                                                                              AppLockConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for appLock"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("appLock"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              AppLockConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 AppLockConfig)))))))))))))))
                                                              :<|> ((Named
                                                                       '("iget", FileSharingConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for fileSharing"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("fileSharing"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                FileSharingConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               FileSharingConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for fileSharing"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("fileSharing"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               FileSharingConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  FileSharingConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    FileSharingConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for fileSharing"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("fileSharing"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    FileSharingConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       FileSharingConfig)))))))))))))))
                                                                    :<|> (Named
                                                                            '("iget",
                                                                              ClassifiedDomainsConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Get config for classifiedDomains"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("classifiedDomains"
                                                                                                             :> Get
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     ClassifiedDomainsConfig))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     ConferenceCallingConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for conferenceCalling"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("conferenceCalling"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            ConferenceCallingConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           ConferenceCallingConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for conferenceCalling"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("conferenceCalling"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           ConferenceCallingConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              ConferenceCallingConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                ConferenceCallingConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for conferenceCalling"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("conferenceCalling"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                ConferenceCallingConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   ConferenceCallingConfig)))))))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           SelfDeletingMessagesConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for selfDeletingMessages"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("selfDeletingMessages"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  SelfDeletingMessagesConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 SelfDeletingMessagesConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for selfDeletingMessages"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("selfDeletingMessages"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 SelfDeletingMessagesConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    SelfDeletingMessagesConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      SelfDeletingMessagesConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for selfDeletingMessages"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("selfDeletingMessages"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      SelfDeletingMessagesConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         SelfDeletingMessagesConfig)))))))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 GuestLinksConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for conversationGuestLinks"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("conversationGuestLinks"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        GuestLinksConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       GuestLinksConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for conversationGuestLinks"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("conversationGuestLinks"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       GuestLinksConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          GuestLinksConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            GuestLinksConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for conversationGuestLinks"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("conversationGuestLinks"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            GuestLinksConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               GuestLinksConfig)))))))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       SndFactorPasswordChallengeConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for sndFactorPasswordChallenge"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("sndFactorPasswordChallenge"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              SndFactorPasswordChallengeConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             SndFactorPasswordChallengeConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for sndFactorPasswordChallenge"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("sndFactorPasswordChallenge"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             SndFactorPasswordChallengeConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                SndFactorPasswordChallengeConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for sndFactorPasswordChallenge"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("sndFactorPasswordChallenge"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             MLSConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for mls"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("mls"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    MLSConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   MLSConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for mls"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("mls"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   MLSConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      MLSConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        MLSConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for mls"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("mls"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        MLSConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           MLSConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         OutlookCalIntegrationConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for outlookCalIntegration"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("outlookCalIntegration"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                OutlookCalIntegrationConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               OutlookCalIntegrationConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for outlookCalIntegration"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("outlookCalIntegration"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               OutlookCalIntegrationConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  OutlookCalIntegrationConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    OutlookCalIntegrationConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for outlookCalIntegration"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("outlookCalIntegration"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    OutlookCalIntegrationConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       OutlookCalIntegrationConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               MlsE2EIdConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for mlsE2EId"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("mlsE2EId"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      MlsE2EIdConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     MlsE2EIdConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for mlsE2EId"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("mlsE2EId"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     MlsE2EIdConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        MlsE2EIdConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          MlsE2EIdConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for mlsE2EId"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("mlsE2EId"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          MlsE2EIdConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             MlsE2EIdConfig)))))))))))))))
                                                                                                                          :<|> ((Named
                                                                                                                                   '("iget",
                                                                                                                                     MlsMigrationConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for mlsMigration"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("mlsMigration"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MlsMigrationConfig))))))))))
                                                                                                                                 :<|> (Named
                                                                                                                                         '("iput",
                                                                                                                                           MlsMigrationConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Put config for mlsMigration"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("mlsMigration"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Feature
                                                                                                                                                                                           MlsMigrationConfig)
                                                                                                                                                                                      :> Put
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              MlsMigrationConfig)))))))))))))
                                                                                                                                       :<|> Named
                                                                                                                                              '("ipatch",
                                                                                                                                                MlsMigrationConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Patch config for mlsMigration"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("mlsMigration"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                MlsMigrationConfig)
                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   MlsMigrationConfig)))))))))))))))
                                                                                                                                :<|> ((Named
                                                                                                                                         '("iget",
                                                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                                                         (Description
                                                                                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for enforceFileDownloadLocation"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("enforceFileDownloadLocation"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                       :<|> (Named
                                                                                                                                               '("iput",
                                                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                                                               (Description
                                                                                                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                :> (Summary
                                                                                                                                                      "Put config for enforceFileDownloadLocation"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          ('MissingPermission
                                                                                                                                                             'Nothing)
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                          '[]
                                                                                                                                                                        :> ("teams"
                                                                                                                                                                            :> (Capture
                                                                                                                                                                                  "tid"
                                                                                                                                                                                  TeamId
                                                                                                                                                                                :> ("features"
                                                                                                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (Feature
                                                                                                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                                                                                                            :> Put
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                             :<|> Named
                                                                                                                                                    '("ipatch",
                                                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                                                    (Description
                                                                                                                                                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Patch config for enforceFileDownloadLocation"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("enforceFileDownloadLocation"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                 :> Patch
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                      :<|> (Named
                                                                                                                                              '("iget",
                                                                                                                                                LimitedEventFanoutConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Get config for limitedEventFanout"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("teams"
                                                                                                                                                                   :> (Capture
                                                                                                                                                                         "tid"
                                                                                                                                                                         TeamId
                                                                                                                                                                       :> ("features"
                                                                                                                                                                           :> ("limitedEventFanout"
                                                                                                                                                                               :> Get
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       LimitedEventFanoutConfig))))))))))
                                                                                                                                            :<|> (Named
                                                                                                                                                    '("iput",
                                                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                                                    (Description
                                                                                                                                                       ""
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Put config for limitedEventFanout"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('MissingPermission
                                                                                                                                                                  'Nothing)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("limitedEventFanout"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (Feature
                                                                                                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                                                                                                 :> Put
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         LimitedEventFanoutConfig)))))))))))))
                                                                                                                                                  :<|> Named
                                                                                                                                                         '("ipatch",
                                                                                                                                                           LimitedEventFanoutConfig)
                                                                                                                                                         (Description
                                                                                                                                                            ""
                                                                                                                                                          :> (Summary
                                                                                                                                                                "Patch config for limitedEventFanout"
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    ('MissingPermission
                                                                                                                                                                       'Nothing)
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                TeamFeatureError
                                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                                    '[]
                                                                                                                                                                                  :> ("teams"
                                                                                                                                                                                      :> (Capture
                                                                                                                                                                                            "tid"
                                                                                                                                                                                            TeamId
                                                                                                                                                                                          :> ("features"
                                                                                                                                                                                              :> ("limitedEventFanout"
                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        (LockableFeaturePatch
                                                                                                                                                                                                           LimitedEventFanoutConfig)
                                                                                                                                                                                                      :> Patch
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                                              LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                         :<|> (Named
                                 '("ilock", FileSharingConfig)
                                 (Summary "(Un-)lock fileSharing"
                                  :> (Description ""
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("fileSharing"
                                                              :> (Capture "lockStatus" LockStatus
                                                                  :> Put
                                                                       '[JSON]
                                                                       LockStatusResponse)))))))))
                               :<|> (Named
                                       '("ilock", ConferenceCallingConfig)
                                       (Summary "(Un-)lock conferenceCalling"
                                        :> (Description ""
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("conferenceCalling"
                                                                    :> (Capture
                                                                          "lockStatus" LockStatus
                                                                        :> Put
                                                                             '[JSON]
                                                                             LockStatusResponse)))))))))
                                     :<|> (Named
                                             '("ilock", SelfDeletingMessagesConfig)
                                             (Summary "(Un-)lock selfDeletingMessages"
                                              :> (Description ""
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("selfDeletingMessages"
                                                                          :> (Capture
                                                                                "lockStatus"
                                                                                LockStatus
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   LockStatusResponse)))))))))
                                           :<|> (Named
                                                   '("ilock", GuestLinksConfig)
                                                   (Summary "(Un-)lock conversationGuestLinks"
                                                    :> (Description ""
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("conversationGuestLinks"
                                                                                :> (Capture
                                                                                      "lockStatus"
                                                                                      LockStatus
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         LockStatusResponse)))))))))
                                                 :<|> (Named
                                                         '("ilock",
                                                           SndFactorPasswordChallengeConfig)
                                                         (Summary
                                                            "(Un-)lock sndFactorPasswordChallenge"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("sndFactorPasswordChallenge"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock", MLSConfig)
                                                               (Summary "(Un-)lock mls"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mls"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock",
                                                                       OutlookCalIntegrationConfig)
                                                                     (Summary
                                                                        "(Un-)lock outlookCalIntegration"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("outlookCalIntegration"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock",
                                                                             MlsE2EIdConfig)
                                                                           (Summary
                                                                              "(Un-)lock mlsE2EId"
                                                                            :> (Description ""
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mlsE2EId"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("ilock",
                                                                                   MlsMigrationConfig)
                                                                                 (Summary
                                                                                    "(Un-)lock mlsMigration"
                                                                                  :> (Description ""
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mlsMigration"
                                                                                                              :> (Capture
                                                                                                                    "lockStatus"
                                                                                                                    LockStatus
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       LockStatusResponse)))))))))
                                                                               :<|> (Named
                                                                                       '("ilock",
                                                                                         EnforceFileDownloadLocationConfig)
                                                                                       (Summary
                                                                                          "(Un-)lock enforceFileDownloadLocation"
                                                                                        :> (Description
                                                                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                    :> (Capture
                                                                                                                          "lockStatus"
                                                                                                                          LockStatus
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             LockStatusResponse)))))))))
                                                                                     :<|> (Named
                                                                                             '("igetmulti",
                                                                                               SearchVisibilityInboundConfig)
                                                                                             (Summary
                                                                                                "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                              :> ("features-multi-teams"
                                                                                                  :> ("searchVisibilityInbound"
                                                                                                      :> (ReqBody
                                                                                                            '[JSON]
                                                                                                            TeamFeatureNoConfigMultiRequest
                                                                                                          :> Post
                                                                                                               '[JSON]
                                                                                                               (TeamFeatureNoConfigMultiResponse
                                                                                                                  SearchVisibilityInboundConfig)))))
                                                                                           :<|> Named
                                                                                                  "feature-configs-internal"
                                                                                                  (Summary
                                                                                                     "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                                   :> ("feature-configs"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (QueryParam'
                                                                                                                         '[Optional,
                                                                                                                           Strict,
                                                                                                                           Description
                                                                                                                             "Optional user id"]
                                                                                                                         "user_id"
                                                                                                                         UserId
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            AllTeamFeatures))))))))))))))))))
                        :<|> (IFederationAPI :<|> (IConversationAPI :<|> IEJPDAPI))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     "get-team-members"
     (CanThrow 'NonBindingTeam
      :> (CanThrow 'TeamNotFound
          :> ("users"
              :> (Capture "uid" UserId
                  :> ("team" :> ("members" :> Get '[JSON] TeamMemberList))))))
   :<|> (Named
           "get-team-id"
           (CanThrow 'NonBindingTeam
            :> (CanThrow 'TeamNotFound
                :> ("users"
                    :> (Capture "uid" UserId :> ("team" :> Get '[JSON] TeamId)))))
         :<|> (Named
                 "test-get-clients"
                 ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
               :<|> (Named
                       "test-add-client"
                       ("clients"
                        :> (ZUser
                            :> (Capture "cid" ClientId
                                :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
                     :<|> (Named
                             "test-delete-client"
                             ("clients"
                              :> (ZUser
                                  :> (Capture "cid" ClientId
                                      :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
                           :<|> (Named
                                   "add-service"
                                   ("services"
                                    :> (ReqBody '[JSON] Service
                                        :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
                                 :<|> (Named
                                         "delete-service"
                                         ("services"
                                          :> (ReqBody '[JSON] ServiceRef
                                              :> MultiVerb
                                                   'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
                                       :<|> (Named
                                               "i-add-bot"
                                               (CanThrow ('ActionDenied 'AddConversationMember)
                                                :> (CanThrow 'ConvNotFound
                                                    :> (CanThrow 'InvalidOperation
                                                        :> (CanThrow 'TooManyMembers
                                                            :> ("bots"
                                                                :> (ZLocalUser
                                                                    :> (ZConn
                                                                        :> (ReqBody '[JSON] AddBot
                                                                            :> Post
                                                                                 '[JSON]
                                                                                 Event))))))))
                                             :<|> (Named
                                                     "delete-bot"
                                                     (CanThrow 'ConvNotFound
                                                      :> (CanThrow
                                                            ('ActionDenied
                                                               'RemoveConversationMember)
                                                          :> ("bots"
                                                              :> (ZLocalUser
                                                                  :> (ZOptConn
                                                                      :> (ReqBody '[JSON] RemoveBot
                                                                          :> MultiVerb
                                                                               'DELETE
                                                                               '[JSON]
                                                                               (UpdateResponses
                                                                                  "Bot not found"
                                                                                  "Bot deleted"
                                                                                  Event)
                                                                               (UpdateResult
                                                                                  Event)))))))
                                                   :<|> (Named
                                                           "put-custom-backend"
                                                           ("custom-backend"
                                                            :> ("by-domain"
                                                                :> (Capture "domain" Domain
                                                                    :> (ReqBody
                                                                          '[JSON] CustomBackend
                                                                        :> MultiVerb
                                                                             'PUT
                                                                             '[JSON]
                                                                             '[RespondEmpty
                                                                                 201 "OK"]
                                                                             ()))))
                                                         :<|> Named
                                                                "delete-custom-backend"
                                                                ("custom-backend"
                                                                 :> ("by-domain"
                                                                     :> (Capture "domain" Domain
                                                                         :> 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 IMiscAPI GalleyEffects
miscAPI
      API
  (Named
     "get-team-members"
     (CanThrow 'NonBindingTeam
      :> (CanThrow 'TeamNotFound
          :> ("users"
              :> (Capture "uid" UserId
                  :> ("team" :> ("members" :> Get '[JSON] TeamMemberList))))))
   :<|> (Named
           "get-team-id"
           (CanThrow 'NonBindingTeam
            :> (CanThrow 'TeamNotFound
                :> ("users"
                    :> (Capture "uid" UserId :> ("team" :> Get '[JSON] TeamId)))))
         :<|> (Named
                 "test-get-clients"
                 ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
               :<|> (Named
                       "test-add-client"
                       ("clients"
                        :> (ZUser
                            :> (Capture "cid" ClientId
                                :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
                     :<|> (Named
                             "test-delete-client"
                             ("clients"
                              :> (ZUser
                                  :> (Capture "cid" ClientId
                                      :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
                           :<|> (Named
                                   "add-service"
                                   ("services"
                                    :> (ReqBody '[JSON] Service
                                        :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
                                 :<|> (Named
                                         "delete-service"
                                         ("services"
                                          :> (ReqBody '[JSON] ServiceRef
                                              :> MultiVerb
                                                   'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
                                       :<|> (Named
                                               "i-add-bot"
                                               (CanThrow ('ActionDenied 'AddConversationMember)
                                                :> (CanThrow 'ConvNotFound
                                                    :> (CanThrow 'InvalidOperation
                                                        :> (CanThrow 'TooManyMembers
                                                            :> ("bots"
                                                                :> (ZLocalUser
                                                                    :> (ZConn
                                                                        :> (ReqBody '[JSON] AddBot
                                                                            :> Post
                                                                                 '[JSON]
                                                                                 Event))))))))
                                             :<|> (Named
                                                     "delete-bot"
                                                     (CanThrow 'ConvNotFound
                                                      :> (CanThrow
                                                            ('ActionDenied
                                                               'RemoveConversationMember)
                                                          :> ("bots"
                                                              :> (ZLocalUser
                                                                  :> (ZOptConn
                                                                      :> (ReqBody '[JSON] RemoveBot
                                                                          :> MultiVerb
                                                                               'DELETE
                                                                               '[JSON]
                                                                               (UpdateResponses
                                                                                  "Bot not found"
                                                                                  "Bot deleted"
                                                                                  Event)
                                                                               (UpdateResult
                                                                                  Event)))))))
                                                   :<|> (Named
                                                           "put-custom-backend"
                                                           ("custom-backend"
                                                            :> ("by-domain"
                                                                :> (Capture "domain" Domain
                                                                    :> (ReqBody
                                                                          '[JSON] CustomBackend
                                                                        :> MultiVerb
                                                                             'PUT
                                                                             '[JSON]
                                                                             '[RespondEmpty
                                                                                 201 "OK"]
                                                                             ()))))
                                                         :<|> Named
                                                                "delete-custom-backend"
                                                                ("custom-backend"
                                                                 :> ("by-domain"
                                                                     :> (Capture "domain" Domain
                                                                         :> 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
        "upsert-one2one"
        (Summary "Create or Update a connect or one2one conversation."
         :> ("conversations"
             :> ("one2one"
                 :> ("upsert"
                     :> (ReqBody '[JSON] UpsertOne2OneConversationRequest
                         :> MultiVerb
                              'POST '[JSON] '[RespondEmpty 200 "Upsert One2One Policy"] ())))))
      :<|> ((((Named
                 '("iget", LegalholdConfig)
                 (Description ""
                  :> (Summary "Get config for legalhold"
                      :> (CanThrow ('MissingPermission 'Nothing)
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("legalhold"
                                                  :> Get
                                                       '[JSON]
                                                       (LockableFeature LegalholdConfig))))))))))
               :<|> (Named
                       '("iput", LegalholdConfig)
                       (Description ""
                        :> (Summary "Put config for legalhold"
                            :> (CanThrow ('MissingPermission 'Nothing)
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> (CanThrow TeamFeatureError
                                            :> (CanThrowMany
                                                  '[ 'ActionDenied 'RemoveConversationMember,
                                                     'CannotEnableLegalHoldServiceLargeTeam,
                                                     'LegalHoldNotEnabled,
                                                     'LegalHoldDisableUnimplemented,
                                                     'LegalHoldServiceNotRegistered,
                                                     'UserLegalHoldIllegalOperation,
                                                     'LegalHoldCouldNotBlockConnections]
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("legalhold"
                                                                :> (ReqBody
                                                                      '[JSON]
                                                                      (Feature LegalholdConfig)
                                                                    :> Put
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            LegalholdConfig)))))))))))))
                     :<|> Named
                            '("ipatch", LegalholdConfig)
                            (Description ""
                             :> (Summary "Patch config for legalhold"
                                 :> (CanThrow ('MissingPermission 'Nothing)
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow TeamFeatureError
                                                 :> (CanThrowMany
                                                       '[ 'ActionDenied 'RemoveConversationMember,
                                                          'CannotEnableLegalHoldServiceLargeTeam,
                                                          'LegalHoldNotEnabled,
                                                          'LegalHoldDisableUnimplemented,
                                                          'LegalHoldServiceNotRegistered,
                                                          'UserLegalHoldIllegalOperation,
                                                          'LegalHoldCouldNotBlockConnections]
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("legalhold"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           (LockableFeaturePatch
                                                                              LegalholdConfig)
                                                                         :> Patch
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 LegalholdConfig)))))))))))))))
              :<|> ((Named
                       '("iget", SSOConfig)
                       (Description ""
                        :> (Summary "Get config for sso"
                            :> (CanThrow ('MissingPermission 'Nothing)
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("sso"
                                                        :> Get
                                                             '[JSON]
                                                             (LockableFeature SSOConfig))))))))))
                     :<|> (Named
                             '("iput", SSOConfig)
                             (Description ""
                              :> (Summary "Put config for sso"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> (CanThrow TeamFeatureError
                                                  :> (CanThrowMany '[]
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("sso"
                                                                      :> (ReqBody
                                                                            '[JSON]
                                                                            (Feature SSOConfig)
                                                                          :> Put
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  SSOConfig)))))))))))))
                           :<|> Named
                                  '("ipatch", SSOConfig)
                                  (Description ""
                                   :> (Summary "Patch config for sso"
                                       :> (CanThrow ('MissingPermission 'Nothing)
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany '[]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("sso"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (LockableFeaturePatch
                                                                                    SSOConfig)
                                                                               :> Patch
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       SSOConfig)))))))))))))))
                    :<|> ((Named
                             '("iget", SearchVisibilityAvailableConfig)
                             (Description ""
                              :> (Summary "Get config for searchVisibility"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("searchVisibility"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      SearchVisibilityAvailableConfig))))))))))
                           :<|> (Named
                                   '("iput", SearchVisibilityAvailableConfig)
                                   (Description ""
                                    :> (Summary "Put config for searchVisibility"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> (CanThrow TeamFeatureError
                                                        :> (CanThrowMany '[]
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("searchVisibility"
                                                                            :> (ReqBody
                                                                                  '[JSON]
                                                                                  (Feature
                                                                                     SearchVisibilityAvailableConfig)
                                                                                :> Put
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SearchVisibilityAvailableConfig)))))))))))))
                                 :<|> Named
                                        '("ipatch", SearchVisibilityAvailableConfig)
                                        (Description ""
                                         :> (Summary "Patch config for searchVisibility"
                                             :> (CanThrow ('MissingPermission 'Nothing)
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("searchVisibility"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (LockableFeaturePatch
                                                                                          SearchVisibilityAvailableConfig)
                                                                                     :> Patch
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             SearchVisibilityAvailableConfig)))))))))))))))
                          :<|> ((Named
                                   '("iget", SearchVisibilityInboundConfig)
                                   (Description ""
                                    :> (Summary "Get config for searchVisibilityInbound"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("searchVisibilityInbound"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            SearchVisibilityInboundConfig))))))))))
                                 :<|> (Named
                                         '("iput", SearchVisibilityInboundConfig)
                                         (Description ""
                                          :> (Summary "Put config for searchVisibilityInbound"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow TeamFeatureError
                                                              :> (CanThrowMany '[]
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("searchVisibilityInbound"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        (Feature
                                                                                           SearchVisibilityInboundConfig)
                                                                                      :> Put
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              SearchVisibilityInboundConfig)))))))))))))
                                       :<|> Named
                                              '("ipatch", SearchVisibilityInboundConfig)
                                              (Description ""
                                               :> (Summary
                                                     "Patch config for searchVisibilityInbound"
                                                   :> (CanThrow ('MissingPermission 'Nothing)
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("searchVisibilityInbound"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (LockableFeaturePatch
                                                                                                SearchVisibilityInboundConfig)
                                                                                           :> Patch
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   SearchVisibilityInboundConfig)))))))))))))))
                                :<|> ((Named
                                         '("iget", ValidateSAMLEmailsConfig)
                                         (Description ""
                                          :> (Summary "Get config for validateSAMLemails"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("validateSAMLemails"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  ValidateSAMLEmailsConfig))))))))))
                                       :<|> (Named
                                               '("iput", ValidateSAMLEmailsConfig)
                                               (Description ""
                                                :> (Summary "Put config for validateSAMLemails"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> (CanThrowMany '[]
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("validateSAMLemails"
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              (Feature
                                                                                                 ValidateSAMLEmailsConfig)
                                                                                            :> Put
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    ValidateSAMLEmailsConfig)))))))))))))
                                             :<|> Named
                                                    '("ipatch", ValidateSAMLEmailsConfig)
                                                    (Description ""
                                                     :> (Summary
                                                           "Patch config for validateSAMLemails"
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("validateSAMLemails"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (LockableFeaturePatch
                                                                                                      ValidateSAMLEmailsConfig)
                                                                                                 :> Patch
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         ValidateSAMLEmailsConfig)))))))))))))))
                                      :<|> ((Named
                                               '("iget", DigitalSignaturesConfig)
                                               (Description ""
                                                :> (Summary "Get config for digitalSignatures"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("digitalSignatures"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        DigitalSignaturesConfig))))))))))
                                             :<|> (Named
                                                     '("iput", DigitalSignaturesConfig)
                                                     (Description ""
                                                      :> (Summary "Put config for digitalSignatures"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany '[]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("digitalSignatures"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (Feature
                                                                                                       DigitalSignaturesConfig)
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          DigitalSignaturesConfig)))))))))))))
                                                   :<|> Named
                                                          '("ipatch", DigitalSignaturesConfig)
                                                          (Description ""
                                                           :> (Summary
                                                                 "Patch config for digitalSignatures"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("digitalSignatures"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (LockableFeaturePatch
                                                                                                            DigitalSignaturesConfig)
                                                                                                       :> Patch
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               DigitalSignaturesConfig)))))))))))))))
                                            :<|> ((Named
                                                     '("iget", AppLockConfig)
                                                     (Description ""
                                                      :> (Summary "Get config for appLock"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("appLock"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              AppLockConfig))))))))))
                                                   :<|> (Named
                                                           '("iput", AppLockConfig)
                                                           (Description ""
                                                            :> (Summary "Put config for appLock"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("appLock"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             AppLockConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                AppLockConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch", AppLockConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Patch config for appLock"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("appLock"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  AppLockConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     AppLockConfig)))))))))))))))
                                                  :<|> ((Named
                                                           '("iget", FileSharingConfig)
                                                           (Description ""
                                                            :> (Summary "Get config for fileSharing"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("fileSharing"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    FileSharingConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput", FileSharingConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Put config for fileSharing"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("fileSharing"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   FileSharingConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      FileSharingConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch", FileSharingConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for fileSharing"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("fileSharing"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        FileSharingConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           FileSharingConfig)))))))))))))))
                                                        :<|> (Named
                                                                '("iget", ClassifiedDomainsConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Get config for classifiedDomains"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("classifiedDomains"
                                                                                                 :> Get
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         ClassifiedDomainsConfig))))))))))
                                                              :<|> ((Named
                                                                       '("iget",
                                                                         ConferenceCallingConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for conferenceCalling"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("conferenceCalling"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                ConferenceCallingConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               ConferenceCallingConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for conferenceCalling"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("conferenceCalling"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               ConferenceCallingConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  ConferenceCallingConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    ConferenceCallingConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for conferenceCalling"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("conferenceCalling"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    ConferenceCallingConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       ConferenceCallingConfig)))))))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               SelfDeletingMessagesConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for selfDeletingMessages"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("selfDeletingMessages"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      SelfDeletingMessagesConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     SelfDeletingMessagesConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for selfDeletingMessages"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("selfDeletingMessages"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     SelfDeletingMessagesConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        SelfDeletingMessagesConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          SelfDeletingMessagesConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for selfDeletingMessages"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("selfDeletingMessages"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          SelfDeletingMessagesConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             SelfDeletingMessagesConfig)))))))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     GuestLinksConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for conversationGuestLinks"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("conversationGuestLinks"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            GuestLinksConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           GuestLinksConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for conversationGuestLinks"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("conversationGuestLinks"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           GuestLinksConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              GuestLinksConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                GuestLinksConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for conversationGuestLinks"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                GuestLinksConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   GuestLinksConfig)))))))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           SndFactorPasswordChallengeConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for sndFactorPasswordChallenge"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("sndFactorPasswordChallenge"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  SndFactorPasswordChallengeConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 SndFactorPasswordChallengeConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for sndFactorPasswordChallenge"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("sndFactorPasswordChallenge"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 SndFactorPasswordChallengeConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    SndFactorPasswordChallengeConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for sndFactorPasswordChallenge"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 MLSConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for mls"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mls"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        MLSConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       MLSConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for mls"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("mls"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       MLSConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          MLSConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            MLSConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for mls"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("mls"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            MLSConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               MLSConfig)))))))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             OutlookCalIntegrationConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for outlookCalIntegration"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("outlookCalIntegration"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    OutlookCalIntegrationConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   OutlookCalIntegrationConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for outlookCalIntegration"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("outlookCalIntegration"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   OutlookCalIntegrationConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      OutlookCalIntegrationConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        OutlookCalIntegrationConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for outlookCalIntegration"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("outlookCalIntegration"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        OutlookCalIntegrationConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           OutlookCalIntegrationConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   MlsE2EIdConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for mlsE2EId"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("mlsE2EId"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          MlsE2EIdConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         MlsE2EIdConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for mlsE2EId"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("mlsE2EId"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         MlsE2EIdConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MlsE2EIdConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              MlsE2EIdConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for mlsE2EId"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("mlsE2EId"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              MlsE2EIdConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 MlsE2EIdConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         MlsMigrationConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for mlsMigration"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("mlsMigration"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                MlsMigrationConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               MlsMigrationConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for mlsMigration"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("mlsMigration"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               MlsMigrationConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  MlsMigrationConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    MlsMigrationConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for mlsMigration"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("mlsMigration"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    MlsMigrationConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       MlsMigrationConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                             (Description
                                                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for enforceFileDownloadLocation"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      EnforceFileDownloadLocationConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                                                   (Description
                                                                                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for enforceFileDownloadLocation"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("enforceFileDownloadLocation"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                                        (Description
                                                                                                                                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for enforceFileDownloadLocation"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("enforceFileDownloadLocation"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                          :<|> (Named
                                                                                                                                  '("iget",
                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Get config for limitedEventFanout"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("teams"
                                                                                                                                                       :> (Capture
                                                                                                                                                             "tid"
                                                                                                                                                             TeamId
                                                                                                                                                           :> ("features"
                                                                                                                                                               :> ("limitedEventFanout"
                                                                                                                                                                   :> Get
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           LimitedEventFanoutConfig))))))))))
                                                                                                                                :<|> (Named
                                                                                                                                        '("iput",
                                                                                                                                          LimitedEventFanoutConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Put config for limitedEventFanout"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("limitedEventFanout"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (Feature
                                                                                                                                                                                          LimitedEventFanoutConfig)
                                                                                                                                                                                     :> Put
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             LimitedEventFanoutConfig)))))))))))))
                                                                                                                                      :<|> Named
                                                                                                                                             '("ipatch",
                                                                                                                                               LimitedEventFanoutConfig)
                                                                                                                                             (Description
                                                                                                                                                ""
                                                                                                                                              :> (Summary
                                                                                                                                                    "Patch config for limitedEventFanout"
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        ('MissingPermission
                                                                                                                                                           'Nothing)
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'NotATeamMember
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                'TeamNotFound
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    TeamFeatureError
                                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                                        '[]
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("limitedEventFanout"
                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            (LockableFeaturePatch
                                                                                                                                                                                               LimitedEventFanoutConfig)
                                                                                                                                                                                          :> Patch
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                                  LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
             :<|> (Named
                     '("ilock", FileSharingConfig)
                     (Summary "(Un-)lock fileSharing"
                      :> (Description ""
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("fileSharing"
                                                  :> (Capture "lockStatus" LockStatus
                                                      :> Put '[JSON] LockStatusResponse)))))))))
                   :<|> (Named
                           '("ilock", ConferenceCallingConfig)
                           (Summary "(Un-)lock conferenceCalling"
                            :> (Description ""
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("conferenceCalling"
                                                        :> (Capture "lockStatus" LockStatus
                                                            :> Put
                                                                 '[JSON] LockStatusResponse)))))))))
                         :<|> (Named
                                 '("ilock", SelfDeletingMessagesConfig)
                                 (Summary "(Un-)lock selfDeletingMessages"
                                  :> (Description ""
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("selfDeletingMessages"
                                                              :> (Capture "lockStatus" LockStatus
                                                                  :> Put
                                                                       '[JSON]
                                                                       LockStatusResponse)))))))))
                               :<|> (Named
                                       '("ilock", GuestLinksConfig)
                                       (Summary "(Un-)lock conversationGuestLinks"
                                        :> (Description ""
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("conversationGuestLinks"
                                                                    :> (Capture
                                                                          "lockStatus" LockStatus
                                                                        :> Put
                                                                             '[JSON]
                                                                             LockStatusResponse)))))))))
                                     :<|> (Named
                                             '("ilock", SndFactorPasswordChallengeConfig)
                                             (Summary "(Un-)lock sndFactorPasswordChallenge"
                                              :> (Description ""
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("sndFactorPasswordChallenge"
                                                                          :> (Capture
                                                                                "lockStatus"
                                                                                LockStatus
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   LockStatusResponse)))))))))
                                           :<|> (Named
                                                   '("ilock", MLSConfig)
                                                   (Summary "(Un-)lock mls"
                                                    :> (Description ""
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("mls"
                                                                                :> (Capture
                                                                                      "lockStatus"
                                                                                      LockStatus
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         LockStatusResponse)))))))))
                                                 :<|> (Named
                                                         '("ilock", OutlookCalIntegrationConfig)
                                                         (Summary "(Un-)lock outlookCalIntegration"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("outlookCalIntegration"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock", MlsE2EIdConfig)
                                                               (Summary "(Un-)lock mlsE2EId"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mlsE2EId"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock", MlsMigrationConfig)
                                                                     (Summary
                                                                        "(Un-)lock mlsMigration"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mlsMigration"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock",
                                                                             EnforceFileDownloadLocationConfig)
                                                                           (Summary
                                                                              "(Un-)lock enforceFileDownloadLocation"
                                                                            :> (Description
                                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("igetmulti",
                                                                                   SearchVisibilityInboundConfig)
                                                                                 (Summary
                                                                                    "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                  :> ("features-multi-teams"
                                                                                      :> ("searchVisibilityInbound"
                                                                                          :> (ReqBody
                                                                                                '[JSON]
                                                                                                TeamFeatureNoConfigMultiRequest
                                                                                              :> Post
                                                                                                   '[JSON]
                                                                                                   (TeamFeatureNoConfigMultiResponse
                                                                                                      SearchVisibilityInboundConfig)))))
                                                                               :<|> Named
                                                                                      "feature-configs-internal"
                                                                                      (Summary
                                                                                         "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                       :> ("feature-configs"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (QueryParam'
                                                                                                             '[Optional,
                                                                                                               Strict,
                                                                                                               Description
                                                                                                                 "Optional user id"]
                                                                                                             "user_id"
                                                                                                             UserId
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                AllTeamFeatures))))))))))))))))))
            :<|> (IFederationAPI :<|> (IConversationAPI :<|> IEJPDAPI))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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-team-members"
         (CanThrow 'NonBindingTeam
          :> (CanThrow 'TeamNotFound
              :> ("users"
                  :> (Capture "uid" UserId
                      :> ("team" :> ("members" :> Get '[JSON] TeamMemberList))))))
       :<|> (Named
               "get-team-id"
               (CanThrow 'NonBindingTeam
                :> (CanThrow 'TeamNotFound
                    :> ("users"
                        :> (Capture "uid" UserId :> ("team" :> Get '[JSON] TeamId)))))
             :<|> (Named
                     "test-get-clients"
                     ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
                   :<|> (Named
                           "test-add-client"
                           ("clients"
                            :> (ZUser
                                :> (Capture "cid" ClientId
                                    :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
                         :<|> (Named
                                 "test-delete-client"
                                 ("clients"
                                  :> (ZUser
                                      :> (Capture "cid" ClientId
                                          :> MultiVerb
                                               'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
                               :<|> (Named
                                       "add-service"
                                       ("services"
                                        :> (ReqBody '[JSON] Service
                                            :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
                                     :<|> (Named
                                             "delete-service"
                                             ("services"
                                              :> (ReqBody '[JSON] ServiceRef
                                                  :> MultiVerb
                                                       'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
                                           :<|> (Named
                                                   "i-add-bot"
                                                   (CanThrow ('ActionDenied 'AddConversationMember)
                                                    :> (CanThrow 'ConvNotFound
                                                        :> (CanThrow 'InvalidOperation
                                                            :> (CanThrow 'TooManyMembers
                                                                :> ("bots"
                                                                    :> (ZLocalUser
                                                                        :> (ZConn
                                                                            :> (ReqBody
                                                                                  '[JSON] AddBot
                                                                                :> Post
                                                                                     '[JSON]
                                                                                     Event))))))))
                                                 :<|> (Named
                                                         "delete-bot"
                                                         (CanThrow 'ConvNotFound
                                                          :> (CanThrow
                                                                ('ActionDenied
                                                                   'RemoveConversationMember)
                                                              :> ("bots"
                                                                  :> (ZLocalUser
                                                                      :> (ZOptConn
                                                                          :> (ReqBody
                                                                                '[JSON] RemoveBot
                                                                              :> MultiVerb
                                                                                   'DELETE
                                                                                   '[JSON]
                                                                                   (UpdateResponses
                                                                                      "Bot not found"
                                                                                      "Bot deleted"
                                                                                      Event)
                                                                                   (UpdateResult
                                                                                      Event)))))))
                                                       :<|> (Named
                                                               "put-custom-backend"
                                                               ("custom-backend"
                                                                :> ("by-domain"
                                                                    :> (Capture "domain" Domain
                                                                        :> (ReqBody
                                                                              '[JSON] CustomBackend
                                                                            :> MultiVerb
                                                                                 'PUT
                                                                                 '[JSON]
                                                                                 '[RespondEmpty
                                                                                     201 "OK"]
                                                                                 ()))))
                                                             :<|> Named
                                                                    "delete-custom-backend"
                                                                    ("custom-backend"
                                                                     :> ("by-domain"
                                                                         :> (Capture "domain" Domain
                                                                             :> MultiVerb
                                                                                  'DELETE
                                                                                  '[JSON]
                                                                                  '[RespondEmpty
                                                                                      200 "OK"]
                                                                                  ())))))))))))))
      :<|> (Named
              "upsert-one2one"
              (Summary "Create or Update a connect or one2one conversation."
               :> ("conversations"
                   :> ("one2one"
                       :> ("upsert"
                           :> (ReqBody '[JSON] UpsertOne2OneConversationRequest
                               :> MultiVerb
                                    'POST
                                    '[JSON]
                                    '[RespondEmpty 200 "Upsert One2One Policy"]
                                    ())))))
            :<|> ((((Named
                       '("iget", LegalholdConfig)
                       (Description ""
                        :> (Summary "Get config for legalhold"
                            :> (CanThrow ('MissingPermission 'Nothing)
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("legalhold"
                                                        :> Get
                                                             '[JSON]
                                                             (LockableFeature
                                                                LegalholdConfig))))))))))
                     :<|> (Named
                             '("iput", LegalholdConfig)
                             (Description ""
                              :> (Summary "Put config for legalhold"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> (CanThrow TeamFeatureError
                                                  :> (CanThrowMany
                                                        '[ 'ActionDenied 'RemoveConversationMember,
                                                           'CannotEnableLegalHoldServiceLargeTeam,
                                                           'LegalHoldNotEnabled,
                                                           'LegalHoldDisableUnimplemented,
                                                           'LegalHoldServiceNotRegistered,
                                                           'UserLegalHoldIllegalOperation,
                                                           'LegalHoldCouldNotBlockConnections]
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("legalhold"
                                                                      :> (ReqBody
                                                                            '[JSON]
                                                                            (Feature
                                                                               LegalholdConfig)
                                                                          :> Put
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  LegalholdConfig)))))))))))))
                           :<|> Named
                                  '("ipatch", LegalholdConfig)
                                  (Description ""
                                   :> (Summary "Patch config for legalhold"
                                       :> (CanThrow ('MissingPermission 'Nothing)
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany
                                                             '[ 'ActionDenied
                                                                  'RemoveConversationMember,
                                                                'CannotEnableLegalHoldServiceLargeTeam,
                                                                'LegalHoldNotEnabled,
                                                                'LegalHoldDisableUnimplemented,
                                                                'LegalHoldServiceNotRegistered,
                                                                'UserLegalHoldIllegalOperation,
                                                                'LegalHoldCouldNotBlockConnections]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("legalhold"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (LockableFeaturePatch
                                                                                    LegalholdConfig)
                                                                               :> Patch
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       LegalholdConfig)))))))))))))))
                    :<|> ((Named
                             '("iget", SSOConfig)
                             (Description ""
                              :> (Summary "Get config for sso"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("sso"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      SSOConfig))))))))))
                           :<|> (Named
                                   '("iput", SSOConfig)
                                   (Description ""
                                    :> (Summary "Put config for sso"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> (CanThrow TeamFeatureError
                                                        :> (CanThrowMany '[]
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("sso"
                                                                            :> (ReqBody
                                                                                  '[JSON]
                                                                                  (Feature
                                                                                     SSOConfig)
                                                                                :> Put
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SSOConfig)))))))))))))
                                 :<|> Named
                                        '("ipatch", SSOConfig)
                                        (Description ""
                                         :> (Summary "Patch config for sso"
                                             :> (CanThrow ('MissingPermission 'Nothing)
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("sso"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (LockableFeaturePatch
                                                                                          SSOConfig)
                                                                                     :> Patch
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             SSOConfig)))))))))))))))
                          :<|> ((Named
                                   '("iget", SearchVisibilityAvailableConfig)
                                   (Description ""
                                    :> (Summary "Get config for searchVisibility"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("searchVisibility"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            SearchVisibilityAvailableConfig))))))))))
                                 :<|> (Named
                                         '("iput", SearchVisibilityAvailableConfig)
                                         (Description ""
                                          :> (Summary "Put config for searchVisibility"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow TeamFeatureError
                                                              :> (CanThrowMany '[]
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("searchVisibility"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        (Feature
                                                                                           SearchVisibilityAvailableConfig)
                                                                                      :> Put
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              SearchVisibilityAvailableConfig)))))))))))))
                                       :<|> Named
                                              '("ipatch", SearchVisibilityAvailableConfig)
                                              (Description ""
                                               :> (Summary "Patch config for searchVisibility"
                                                   :> (CanThrow ('MissingPermission 'Nothing)
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("searchVisibility"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (LockableFeaturePatch
                                                                                                SearchVisibilityAvailableConfig)
                                                                                           :> Patch
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   SearchVisibilityAvailableConfig)))))))))))))))
                                :<|> ((Named
                                         '("iget", SearchVisibilityInboundConfig)
                                         (Description ""
                                          :> (Summary "Get config for searchVisibilityInbound"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("searchVisibilityInbound"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  SearchVisibilityInboundConfig))))))))))
                                       :<|> (Named
                                               '("iput", SearchVisibilityInboundConfig)
                                               (Description ""
                                                :> (Summary "Put config for searchVisibilityInbound"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> (CanThrowMany '[]
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("searchVisibilityInbound"
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              (Feature
                                                                                                 SearchVisibilityInboundConfig)
                                                                                            :> Put
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    SearchVisibilityInboundConfig)))))))))))))
                                             :<|> Named
                                                    '("ipatch", SearchVisibilityInboundConfig)
                                                    (Description ""
                                                     :> (Summary
                                                           "Patch config for searchVisibilityInbound"
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("searchVisibilityInbound"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (LockableFeaturePatch
                                                                                                      SearchVisibilityInboundConfig)
                                                                                                 :> Patch
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         SearchVisibilityInboundConfig)))))))))))))))
                                      :<|> ((Named
                                               '("iget", ValidateSAMLEmailsConfig)
                                               (Description ""
                                                :> (Summary "Get config for validateSAMLemails"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("validateSAMLemails"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        ValidateSAMLEmailsConfig))))))))))
                                             :<|> (Named
                                                     '("iput", ValidateSAMLEmailsConfig)
                                                     (Description ""
                                                      :> (Summary
                                                            "Put config for validateSAMLemails"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany '[]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("validateSAMLemails"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (Feature
                                                                                                       ValidateSAMLEmailsConfig)
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          ValidateSAMLEmailsConfig)))))))))))))
                                                   :<|> Named
                                                          '("ipatch", ValidateSAMLEmailsConfig)
                                                          (Description ""
                                                           :> (Summary
                                                                 "Patch config for validateSAMLemails"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("validateSAMLemails"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (LockableFeaturePatch
                                                                                                            ValidateSAMLEmailsConfig)
                                                                                                       :> Patch
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               ValidateSAMLEmailsConfig)))))))))))))))
                                            :<|> ((Named
                                                     '("iget", DigitalSignaturesConfig)
                                                     (Description ""
                                                      :> (Summary "Get config for digitalSignatures"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("digitalSignatures"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              DigitalSignaturesConfig))))))))))
                                                   :<|> (Named
                                                           '("iput", DigitalSignaturesConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Put config for digitalSignatures"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("digitalSignatures"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             DigitalSignaturesConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                DigitalSignaturesConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch", DigitalSignaturesConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Patch config for digitalSignatures"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("digitalSignatures"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  DigitalSignaturesConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     DigitalSignaturesConfig)))))))))))))))
                                                  :<|> ((Named
                                                           '("iget", AppLockConfig)
                                                           (Description ""
                                                            :> (Summary "Get config for appLock"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("appLock"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    AppLockConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput", AppLockConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Put config for appLock"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("appLock"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   AppLockConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      AppLockConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch", AppLockConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for appLock"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("appLock"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        AppLockConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           AppLockConfig)))))))))))))))
                                                        :<|> ((Named
                                                                 '("iget", FileSharingConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Get config for fileSharing"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("fileSharing"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          FileSharingConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput", FileSharingConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for fileSharing"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("fileSharing"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         FileSharingConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            FileSharingConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch",
                                                                              FileSharingConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for fileSharing"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("fileSharing"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              FileSharingConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 FileSharingConfig)))))))))))))))
                                                              :<|> (Named
                                                                      '("iget",
                                                                        ClassifiedDomainsConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Get config for classifiedDomains"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("classifiedDomains"
                                                                                                       :> Get
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               ClassifiedDomainsConfig))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               ConferenceCallingConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for conferenceCalling"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("conferenceCalling"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      ConferenceCallingConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     ConferenceCallingConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for conferenceCalling"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("conferenceCalling"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     ConferenceCallingConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        ConferenceCallingConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          ConferenceCallingConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for conferenceCalling"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("conferenceCalling"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          ConferenceCallingConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             ConferenceCallingConfig)))))))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     SelfDeletingMessagesConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for selfDeletingMessages"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("selfDeletingMessages"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            SelfDeletingMessagesConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           SelfDeletingMessagesConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for selfDeletingMessages"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("selfDeletingMessages"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           SelfDeletingMessagesConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              SelfDeletingMessagesConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                SelfDeletingMessagesConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for selfDeletingMessages"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("selfDeletingMessages"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                SelfDeletingMessagesConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   SelfDeletingMessagesConfig)))))))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           GuestLinksConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for conversationGuestLinks"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("conversationGuestLinks"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  GuestLinksConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 GuestLinksConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for conversationGuestLinks"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("conversationGuestLinks"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 GuestLinksConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    GuestLinksConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      GuestLinksConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for conversationGuestLinks"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      GuestLinksConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         GuestLinksConfig)))))))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 SndFactorPasswordChallengeConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for sndFactorPasswordChallenge"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("sndFactorPasswordChallenge"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        SndFactorPasswordChallengeConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       SndFactorPasswordChallengeConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for sndFactorPasswordChallenge"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("sndFactorPasswordChallenge"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       SndFactorPasswordChallengeConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          SndFactorPasswordChallengeConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for sndFactorPasswordChallenge"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("sndFactorPasswordChallenge"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       MLSConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for mls"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("mls"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              MLSConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             MLSConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for mls"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("mls"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             MLSConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                MLSConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  MLSConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for mls"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("mls"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  MLSConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     MLSConfig)))))))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   OutlookCalIntegrationConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for outlookCalIntegration"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("outlookCalIntegration"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          OutlookCalIntegrationConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         OutlookCalIntegrationConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for outlookCalIntegration"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("outlookCalIntegration"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         OutlookCalIntegrationConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            OutlookCalIntegrationConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              OutlookCalIntegrationConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for outlookCalIntegration"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("outlookCalIntegration"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              OutlookCalIntegrationConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 OutlookCalIntegrationConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         MlsE2EIdConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for mlsE2EId"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("mlsE2EId"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                MlsE2EIdConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               MlsE2EIdConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for mlsE2EId"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("mlsE2EId"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               MlsE2EIdConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  MlsE2EIdConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    MlsE2EIdConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for mlsE2EId"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("mlsE2EId"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    MlsE2EIdConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       MlsE2EIdConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               MlsMigrationConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for mlsMigration"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("mlsMigration"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      MlsMigrationConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     MlsMigrationConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for mlsMigration"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("mlsMigration"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     MlsMigrationConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        MlsMigrationConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          MlsMigrationConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for mlsMigration"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("mlsMigration"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          MlsMigrationConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             MlsMigrationConfig)))))))))))))))
                                                                                                                          :<|> ((Named
                                                                                                                                   '("iget",
                                                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                                                   (Description
                                                                                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for enforceFileDownloadLocation"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                 :<|> (Named
                                                                                                                                         '("iput",
                                                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                                                         (Description
                                                                                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                          :> (Summary
                                                                                                                                                "Put config for enforceFileDownloadLocation"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    ('MissingPermission
                                                                                                                                                       'Nothing)
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Feature
                                                                                                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                                                                                                      :> Put
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                       :<|> Named
                                                                                                                                              '("ipatch",
                                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                                              (Description
                                                                                                                                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                               :> (Summary
                                                                                                                                                     "Patch config for enforceFileDownloadLocation"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("enforceFileDownloadLocation"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                :<|> (Named
                                                                                                                                        '("iget",
                                                                                                                                          LimitedEventFanoutConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Get config for limitedEventFanout"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("teams"
                                                                                                                                                             :> (Capture
                                                                                                                                                                   "tid"
                                                                                                                                                                   TeamId
                                                                                                                                                                 :> ("features"
                                                                                                                                                                     :> ("limitedEventFanout"
                                                                                                                                                                         :> Get
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 LimitedEventFanoutConfig))))))))))
                                                                                                                                      :<|> (Named
                                                                                                                                              '("iput",
                                                                                                                                                LimitedEventFanoutConfig)
                                                                                                                                              (Description
                                                                                                                                                 ""
                                                                                                                                               :> (Summary
                                                                                                                                                     "Put config for limitedEventFanout"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('MissingPermission
                                                                                                                                                            'Nothing)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("limitedEventFanout"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (Feature
                                                                                                                                                                                                LimitedEventFanoutConfig)
                                                                                                                                                                                           :> Put
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   LimitedEventFanoutConfig)))))))))))))
                                                                                                                                            :<|> Named
                                                                                                                                                   '("ipatch",
                                                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                                                   (Description
                                                                                                                                                      ""
                                                                                                                                                    :> (Summary
                                                                                                                                                          "Patch config for limitedEventFanout"
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              ('MissingPermission
                                                                                                                                                                 'Nothing)
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          TeamFeatureError
                                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                                              '[]
                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                :> (Capture
                                                                                                                                                                                      "tid"
                                                                                                                                                                                      TeamId
                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                        :> ("limitedEventFanout"
                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  (LockableFeaturePatch
                                                                                                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                                                                                                :> Patch
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                                        LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                   :<|> (Named
                           '("ilock", FileSharingConfig)
                           (Summary "(Un-)lock fileSharing"
                            :> (Description ""
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("fileSharing"
                                                        :> (Capture "lockStatus" LockStatus
                                                            :> Put
                                                                 '[JSON] LockStatusResponse)))))))))
                         :<|> (Named
                                 '("ilock", ConferenceCallingConfig)
                                 (Summary "(Un-)lock conferenceCalling"
                                  :> (Description ""
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("conferenceCalling"
                                                              :> (Capture "lockStatus" LockStatus
                                                                  :> Put
                                                                       '[JSON]
                                                                       LockStatusResponse)))))))))
                               :<|> (Named
                                       '("ilock", SelfDeletingMessagesConfig)
                                       (Summary "(Un-)lock selfDeletingMessages"
                                        :> (Description ""
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("selfDeletingMessages"
                                                                    :> (Capture
                                                                          "lockStatus" LockStatus
                                                                        :> Put
                                                                             '[JSON]
                                                                             LockStatusResponse)))))))))
                                     :<|> (Named
                                             '("ilock", GuestLinksConfig)
                                             (Summary "(Un-)lock conversationGuestLinks"
                                              :> (Description ""
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("conversationGuestLinks"
                                                                          :> (Capture
                                                                                "lockStatus"
                                                                                LockStatus
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   LockStatusResponse)))))))))
                                           :<|> (Named
                                                   '("ilock", SndFactorPasswordChallengeConfig)
                                                   (Summary "(Un-)lock sndFactorPasswordChallenge"
                                                    :> (Description ""
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("sndFactorPasswordChallenge"
                                                                                :> (Capture
                                                                                      "lockStatus"
                                                                                      LockStatus
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         LockStatusResponse)))))))))
                                                 :<|> (Named
                                                         '("ilock", MLSConfig)
                                                         (Summary "(Un-)lock mls"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("mls"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock",
                                                                 OutlookCalIntegrationConfig)
                                                               (Summary
                                                                  "(Un-)lock outlookCalIntegration"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("outlookCalIntegration"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock", MlsE2EIdConfig)
                                                                     (Summary "(Un-)lock mlsE2EId"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mlsE2EId"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock",
                                                                             MlsMigrationConfig)
                                                                           (Summary
                                                                              "(Un-)lock mlsMigration"
                                                                            :> (Description ""
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mlsMigration"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("ilock",
                                                                                   EnforceFileDownloadLocationConfig)
                                                                                 (Summary
                                                                                    "(Un-)lock enforceFileDownloadLocation"
                                                                                  :> (Description
                                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                              :> (Capture
                                                                                                                    "lockStatus"
                                                                                                                    LockStatus
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       LockStatusResponse)))))))))
                                                                               :<|> (Named
                                                                                       '("igetmulti",
                                                                                         SearchVisibilityInboundConfig)
                                                                                       (Summary
                                                                                          "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                        :> ("features-multi-teams"
                                                                                            :> ("searchVisibilityInbound"
                                                                                                :> (ReqBody
                                                                                                      '[JSON]
                                                                                                      TeamFeatureNoConfigMultiRequest
                                                                                                    :> Post
                                                                                                         '[JSON]
                                                                                                         (TeamFeatureNoConfigMultiResponse
                                                                                                            SearchVisibilityInboundConfig)))))
                                                                                     :<|> Named
                                                                                            "feature-configs-internal"
                                                                                            (Summary
                                                                                               "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                             :> ("feature-configs"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (QueryParam'
                                                                                                                   '[Optional,
                                                                                                                     Strict,
                                                                                                                     Description
                                                                                                                       "Optional user id"]
                                                                                                                   "user_id"
                                                                                                                   UserId
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      AllTeamFeatures))))))))))))))))))
                  :<|> (IFederationAPI :<|> (IConversationAPI :<|> IEJPDAPI)))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"upsert-one2one" ServerT
  (Summary "Create or Update a connect or one2one conversation."
   :> ("conversations"
       :> ("one2one"
           :> ("upsert"
               :> (ReqBody '[JSON] UpsertOne2OneConversationRequest
                   :> MultiVerb
                        'POST '[JSON] '[RespondEmpty 200 "Upsert One2One Policy"] ())))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Create or Update a connect or one2one conversation."
            :> ("conversations"
                :> ("one2one"
                    :> ("upsert"
                        :> (ReqBody '[JSON] UpsertOne2OneConversationRequest
                            :> MultiVerb
                                 'POST '[JSON] '[RespondEmpty 200 "Upsert One2One Policy"] ()))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
UpsertOne2OneConversationRequest
-> 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]
     ()
forall (r :: EffectRow).
(Member ConversationStore r, Member MemberStore r) =>
UpsertOne2OneConversationRequest -> Sem r ()
iUpsertOne2OneConversation
      API
  (Named
     "upsert-one2one"
     (Summary "Create or Update a connect or one2one conversation."
      :> ("conversations"
          :> ("one2one"
              :> ("upsert"
                  :> (ReqBody '[JSON] UpsertOne2OneConversationRequest
                      :> MultiVerb
                           'POST '[JSON] '[RespondEmpty 200 "Upsert One2One Policy"] ()))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
           '("iget", LegalholdConfig)
           (Description ""
            :> (Summary "Get config for legalhold"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> ("teams"
                                :> (Capture "tid" TeamId
                                    :> ("features"
                                        :> ("legalhold"
                                            :> Get
                                                 '[JSON] (LockableFeature LegalholdConfig))))))))))
         :<|> (Named
                 '("iput", LegalholdConfig)
                 (Description ""
                  :> (Summary "Put config for legalhold"
                      :> (CanThrow ('MissingPermission 'Nothing)
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> (CanThrow TeamFeatureError
                                      :> (CanThrowMany
                                            '[ 'ActionDenied 'RemoveConversationMember,
                                               'CannotEnableLegalHoldServiceLargeTeam,
                                               'LegalHoldNotEnabled, 'LegalHoldDisableUnimplemented,
                                               'LegalHoldServiceNotRegistered,
                                               'UserLegalHoldIllegalOperation,
                                               'LegalHoldCouldNotBlockConnections]
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("legalhold"
                                                          :> (ReqBody
                                                                '[JSON] (Feature LegalholdConfig)
                                                              :> Put
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      LegalholdConfig)))))))))))))
               :<|> Named
                      '("ipatch", LegalholdConfig)
                      (Description ""
                       :> (Summary "Patch config for legalhold"
                           :> (CanThrow ('MissingPermission 'Nothing)
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany
                                                 '[ 'ActionDenied 'RemoveConversationMember,
                                                    'CannotEnableLegalHoldServiceLargeTeam,
                                                    'LegalHoldNotEnabled,
                                                    'LegalHoldDisableUnimplemented,
                                                    'LegalHoldServiceNotRegistered,
                                                    'UserLegalHoldIllegalOperation,
                                                    'LegalHoldCouldNotBlockConnections]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("legalhold"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     (LockableFeaturePatch
                                                                        LegalholdConfig)
                                                                   :> Patch
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           LegalholdConfig)))))))))))))))
        :<|> ((Named
                 '("iget", SSOConfig)
                 (Description ""
                  :> (Summary "Get config for sso"
                      :> (CanThrow ('MissingPermission 'Nothing)
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("sso"
                                                  :> Get
                                                       '[JSON] (LockableFeature SSOConfig))))))))))
               :<|> (Named
                       '("iput", SSOConfig)
                       (Description ""
                        :> (Summary "Put config for sso"
                            :> (CanThrow ('MissingPermission 'Nothing)
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> (CanThrow TeamFeatureError
                                            :> (CanThrowMany '[]
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("sso"
                                                                :> (ReqBody
                                                                      '[JSON] (Feature SSOConfig)
                                                                    :> Put
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            SSOConfig)))))))))))))
                     :<|> Named
                            '("ipatch", SSOConfig)
                            (Description ""
                             :> (Summary "Patch config for sso"
                                 :> (CanThrow ('MissingPermission 'Nothing)
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow TeamFeatureError
                                                 :> (CanThrowMany '[]
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("sso"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           (LockableFeaturePatch
                                                                              SSOConfig)
                                                                         :> Patch
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 SSOConfig)))))))))))))))
              :<|> ((Named
                       '("iget", SearchVisibilityAvailableConfig)
                       (Description ""
                        :> (Summary "Get config for searchVisibility"
                            :> (CanThrow ('MissingPermission 'Nothing)
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("searchVisibility"
                                                        :> Get
                                                             '[JSON]
                                                             (LockableFeature
                                                                SearchVisibilityAvailableConfig))))))))))
                     :<|> (Named
                             '("iput", SearchVisibilityAvailableConfig)
                             (Description ""
                              :> (Summary "Put config for searchVisibility"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> (CanThrow TeamFeatureError
                                                  :> (CanThrowMany '[]
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("searchVisibility"
                                                                      :> (ReqBody
                                                                            '[JSON]
                                                                            (Feature
                                                                               SearchVisibilityAvailableConfig)
                                                                          :> Put
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  SearchVisibilityAvailableConfig)))))))))))))
                           :<|> Named
                                  '("ipatch", SearchVisibilityAvailableConfig)
                                  (Description ""
                                   :> (Summary "Patch config for searchVisibility"
                                       :> (CanThrow ('MissingPermission 'Nothing)
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany '[]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("searchVisibility"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (LockableFeaturePatch
                                                                                    SearchVisibilityAvailableConfig)
                                                                               :> Patch
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       SearchVisibilityAvailableConfig)))))))))))))))
                    :<|> ((Named
                             '("iget", SearchVisibilityInboundConfig)
                             (Description ""
                              :> (Summary "Get config for searchVisibilityInbound"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("searchVisibilityInbound"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      SearchVisibilityInboundConfig))))))))))
                           :<|> (Named
                                   '("iput", SearchVisibilityInboundConfig)
                                   (Description ""
                                    :> (Summary "Put config for searchVisibilityInbound"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> (CanThrow TeamFeatureError
                                                        :> (CanThrowMany '[]
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("searchVisibilityInbound"
                                                                            :> (ReqBody
                                                                                  '[JSON]
                                                                                  (Feature
                                                                                     SearchVisibilityInboundConfig)
                                                                                :> Put
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SearchVisibilityInboundConfig)))))))))))))
                                 :<|> Named
                                        '("ipatch", SearchVisibilityInboundConfig)
                                        (Description ""
                                         :> (Summary "Patch config for searchVisibilityInbound"
                                             :> (CanThrow ('MissingPermission 'Nothing)
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("searchVisibilityInbound"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (LockableFeaturePatch
                                                                                          SearchVisibilityInboundConfig)
                                                                                     :> Patch
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             SearchVisibilityInboundConfig)))))))))))))))
                          :<|> ((Named
                                   '("iget", ValidateSAMLEmailsConfig)
                                   (Description ""
                                    :> (Summary "Get config for validateSAMLemails"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("validateSAMLemails"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            ValidateSAMLEmailsConfig))))))))))
                                 :<|> (Named
                                         '("iput", ValidateSAMLEmailsConfig)
                                         (Description ""
                                          :> (Summary "Put config for validateSAMLemails"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow TeamFeatureError
                                                              :> (CanThrowMany '[]
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("validateSAMLemails"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        (Feature
                                                                                           ValidateSAMLEmailsConfig)
                                                                                      :> Put
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              ValidateSAMLEmailsConfig)))))))))))))
                                       :<|> Named
                                              '("ipatch", ValidateSAMLEmailsConfig)
                                              (Description ""
                                               :> (Summary "Patch config for validateSAMLemails"
                                                   :> (CanThrow ('MissingPermission 'Nothing)
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("validateSAMLemails"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (LockableFeaturePatch
                                                                                                ValidateSAMLEmailsConfig)
                                                                                           :> Patch
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   ValidateSAMLEmailsConfig)))))))))))))))
                                :<|> ((Named
                                         '("iget", DigitalSignaturesConfig)
                                         (Description ""
                                          :> (Summary "Get config for digitalSignatures"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("digitalSignatures"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  DigitalSignaturesConfig))))))))))
                                       :<|> (Named
                                               '("iput", DigitalSignaturesConfig)
                                               (Description ""
                                                :> (Summary "Put config for digitalSignatures"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> (CanThrowMany '[]
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("digitalSignatures"
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              (Feature
                                                                                                 DigitalSignaturesConfig)
                                                                                            :> Put
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    DigitalSignaturesConfig)))))))))))))
                                             :<|> Named
                                                    '("ipatch", DigitalSignaturesConfig)
                                                    (Description ""
                                                     :> (Summary
                                                           "Patch config for digitalSignatures"
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("digitalSignatures"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (LockableFeaturePatch
                                                                                                      DigitalSignaturesConfig)
                                                                                                 :> Patch
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         DigitalSignaturesConfig)))))))))))))))
                                      :<|> ((Named
                                               '("iget", AppLockConfig)
                                               (Description ""
                                                :> (Summary "Get config for appLock"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("appLock"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        AppLockConfig))))))))))
                                             :<|> (Named
                                                     '("iput", AppLockConfig)
                                                     (Description ""
                                                      :> (Summary "Put config for appLock"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany '[]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("appLock"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (Feature
                                                                                                       AppLockConfig)
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          AppLockConfig)))))))))))))
                                                   :<|> Named
                                                          '("ipatch", AppLockConfig)
                                                          (Description ""
                                                           :> (Summary "Patch config for appLock"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("appLock"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (LockableFeaturePatch
                                                                                                            AppLockConfig)
                                                                                                       :> Patch
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               AppLockConfig)))))))))))))))
                                            :<|> ((Named
                                                     '("iget", FileSharingConfig)
                                                     (Description ""
                                                      :> (Summary "Get config for fileSharing"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("fileSharing"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              FileSharingConfig))))))))))
                                                   :<|> (Named
                                                           '("iput", FileSharingConfig)
                                                           (Description ""
                                                            :> (Summary "Put config for fileSharing"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("fileSharing"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             FileSharingConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                FileSharingConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch", FileSharingConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Patch config for fileSharing"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("fileSharing"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  FileSharingConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     FileSharingConfig)))))))))))))))
                                                  :<|> (Named
                                                          '("iget", ClassifiedDomainsConfig)
                                                          (Description ""
                                                           :> (Summary
                                                                 "Get config for classifiedDomains"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("classifiedDomains"
                                                                                           :> Get
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   ClassifiedDomainsConfig))))))))))
                                                        :<|> ((Named
                                                                 '("iget", ConferenceCallingConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Get config for conferenceCalling"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("conferenceCalling"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          ConferenceCallingConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput",
                                                                         ConferenceCallingConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for conferenceCalling"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("conferenceCalling"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         ConferenceCallingConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            ConferenceCallingConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch",
                                                                              ConferenceCallingConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for conferenceCalling"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("conferenceCalling"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              ConferenceCallingConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 ConferenceCallingConfig)))))))))))))))
                                                              :<|> ((Named
                                                                       '("iget",
                                                                         SelfDeletingMessagesConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for selfDeletingMessages"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("selfDeletingMessages"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SelfDeletingMessagesConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               SelfDeletingMessagesConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for selfDeletingMessages"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("selfDeletingMessages"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               SelfDeletingMessagesConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  SelfDeletingMessagesConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    SelfDeletingMessagesConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for selfDeletingMessages"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("selfDeletingMessages"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    SelfDeletingMessagesConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       SelfDeletingMessagesConfig)))))))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               GuestLinksConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for conversationGuestLinks"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("conversationGuestLinks"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      GuestLinksConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     GuestLinksConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for conversationGuestLinks"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("conversationGuestLinks"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     GuestLinksConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        GuestLinksConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          GuestLinksConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for conversationGuestLinks"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          GuestLinksConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             GuestLinksConfig)))))))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     SndFactorPasswordChallengeConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for sndFactorPasswordChallenge"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("sndFactorPasswordChallenge"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            SndFactorPasswordChallengeConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           SndFactorPasswordChallengeConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for sndFactorPasswordChallenge"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("sndFactorPasswordChallenge"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           SndFactorPasswordChallengeConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              SndFactorPasswordChallengeConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                SndFactorPasswordChallengeConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for sndFactorPasswordChallenge"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           MLSConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for mls"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mls"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  MLSConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 MLSConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for mls"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("mls"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 MLSConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    MLSConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      MLSConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for mls"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("mls"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      MLSConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         MLSConfig)))))))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       OutlookCalIntegrationConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for outlookCalIntegration"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("outlookCalIntegration"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              OutlookCalIntegrationConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             OutlookCalIntegrationConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for outlookCalIntegration"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("outlookCalIntegration"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             OutlookCalIntegrationConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                OutlookCalIntegrationConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  OutlookCalIntegrationConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for outlookCalIntegration"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("outlookCalIntegration"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  OutlookCalIntegrationConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     OutlookCalIntegrationConfig)))))))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             MlsE2EIdConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for mlsE2EId"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("mlsE2EId"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    MlsE2EIdConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   MlsE2EIdConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for mlsE2EId"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("mlsE2EId"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   MlsE2EIdConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      MlsE2EIdConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        MlsE2EIdConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for mlsE2EId"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("mlsE2EId"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        MlsE2EIdConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           MlsE2EIdConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   MlsMigrationConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for mlsMigration"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("mlsMigration"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          MlsMigrationConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         MlsMigrationConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for mlsMigration"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("mlsMigration"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         MlsMigrationConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MlsMigrationConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              MlsMigrationConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for mlsMigration"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("mlsMigration"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              MlsMigrationConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 MlsMigrationConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         EnforceFileDownloadLocationConfig)
                                                                                                                       (Description
                                                                                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                        :> (Summary
                                                                                                                              "Get config for enforceFileDownloadLocation"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                EnforceFileDownloadLocationConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                             (Description
                                                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for enforceFileDownloadLocation"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                                  (Description
                                                                                                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for enforceFileDownloadLocation"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("enforceFileDownloadLocation"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                    :<|> (Named
                                                                                                                            '("iget",
                                                                                                                              LimitedEventFanoutConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Get config for limitedEventFanout"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("teams"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "tid"
                                                                                                                                                       TeamId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("limitedEventFanout"
                                                                                                                                                             :> Get
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     LimitedEventFanoutConfig))))))))))
                                                                                                                          :<|> (Named
                                                                                                                                  '("iput",
                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Put config for limitedEventFanout"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("limitedEventFanout"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (Feature
                                                                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                                                               :> Put
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       LimitedEventFanoutConfig)))))))))))))
                                                                                                                                :<|> Named
                                                                                                                                       '("ipatch",
                                                                                                                                         LimitedEventFanoutConfig)
                                                                                                                                       (Description
                                                                                                                                          ""
                                                                                                                                        :> (Summary
                                                                                                                                              "Patch config for limitedEventFanout"
                                                                                                                                            :> (CanThrow
                                                                                                                                                  ('MissingPermission
                                                                                                                                                     'Nothing)
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'NotATeamMember
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          'TeamNotFound
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              TeamFeatureError
                                                                                                                                                            :> (CanThrowMany
                                                                                                                                                                  '[]
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("limitedEventFanout"
                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      (LockableFeaturePatch
                                                                                                                                                                                         LimitedEventFanoutConfig)
                                                                                                                                                                                    :> Patch
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                            LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
       :<|> (Named
               '("ilock", FileSharingConfig)
               (Summary "(Un-)lock fileSharing"
                :> (Description ""
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> ("teams"
                                :> (Capture "tid" TeamId
                                    :> ("features"
                                        :> ("fileSharing"
                                            :> (Capture "lockStatus" LockStatus
                                                :> Put '[JSON] LockStatusResponse)))))))))
             :<|> (Named
                     '("ilock", ConferenceCallingConfig)
                     (Summary "(Un-)lock conferenceCalling"
                      :> (Description ""
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("conferenceCalling"
                                                  :> (Capture "lockStatus" LockStatus
                                                      :> Put '[JSON] LockStatusResponse)))))))))
                   :<|> (Named
                           '("ilock", SelfDeletingMessagesConfig)
                           (Summary "(Un-)lock selfDeletingMessages"
                            :> (Description ""
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("selfDeletingMessages"
                                                        :> (Capture "lockStatus" LockStatus
                                                            :> Put
                                                                 '[JSON] LockStatusResponse)))))))))
                         :<|> (Named
                                 '("ilock", GuestLinksConfig)
                                 (Summary "(Un-)lock conversationGuestLinks"
                                  :> (Description ""
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("conversationGuestLinks"
                                                              :> (Capture "lockStatus" LockStatus
                                                                  :> Put
                                                                       '[JSON]
                                                                       LockStatusResponse)))))))))
                               :<|> (Named
                                       '("ilock", SndFactorPasswordChallengeConfig)
                                       (Summary "(Un-)lock sndFactorPasswordChallenge"
                                        :> (Description ""
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("sndFactorPasswordChallenge"
                                                                    :> (Capture
                                                                          "lockStatus" LockStatus
                                                                        :> Put
                                                                             '[JSON]
                                                                             LockStatusResponse)))))))))
                                     :<|> (Named
                                             '("ilock", MLSConfig)
                                             (Summary "(Un-)lock mls"
                                              :> (Description ""
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("mls"
                                                                          :> (Capture
                                                                                "lockStatus"
                                                                                LockStatus
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   LockStatusResponse)))))))))
                                           :<|> (Named
                                                   '("ilock", OutlookCalIntegrationConfig)
                                                   (Summary "(Un-)lock outlookCalIntegration"
                                                    :> (Description ""
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("outlookCalIntegration"
                                                                                :> (Capture
                                                                                      "lockStatus"
                                                                                      LockStatus
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         LockStatusResponse)))))))))
                                                 :<|> (Named
                                                         '("ilock", MlsE2EIdConfig)
                                                         (Summary "(Un-)lock mlsE2EId"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("mlsE2EId"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock", MlsMigrationConfig)
                                                               (Summary "(Un-)lock mlsMigration"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mlsMigration"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock",
                                                                       EnforceFileDownloadLocationConfig)
                                                                     (Summary
                                                                        "(Un-)lock enforceFileDownloadLocation"
                                                                      :> (Description
                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("igetmulti",
                                                                             SearchVisibilityInboundConfig)
                                                                           (Summary
                                                                              "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                            :> ("features-multi-teams"
                                                                                :> ("searchVisibilityInbound"
                                                                                    :> (ReqBody
                                                                                          '[JSON]
                                                                                          TeamFeatureNoConfigMultiRequest
                                                                                        :> Post
                                                                                             '[JSON]
                                                                                             (TeamFeatureNoConfigMultiResponse
                                                                                                SearchVisibilityInboundConfig)))))
                                                                         :<|> Named
                                                                                "feature-configs-internal"
                                                                                (Summary
                                                                                   "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                 :> ("feature-configs"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (QueryParam'
                                                                                                       '[Optional,
                                                                                                         Strict,
                                                                                                         Description
                                                                                                           "Optional user id"]
                                                                                                       "user_id"
                                                                                                       UserId
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          AllTeamFeatures))))))))))))))))))
      :<|> (IFederationAPI :<|> (IConversationAPI :<|> IEJPDAPI)))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "upsert-one2one"
        (Summary "Create or Update a connect or one2one conversation."
         :> ("conversations"
             :> ("one2one"
                 :> ("upsert"
                     :> (ReqBody '[JSON] UpsertOne2OneConversationRequest
                         :> MultiVerb
                              'POST '[JSON] '[RespondEmpty 200 "Upsert One2One Policy"] ())))))
      :<|> ((((Named
                 '("iget", LegalholdConfig)
                 (Description ""
                  :> (Summary "Get config for legalhold"
                      :> (CanThrow ('MissingPermission 'Nothing)
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("legalhold"
                                                  :> Get
                                                       '[JSON]
                                                       (LockableFeature LegalholdConfig))))))))))
               :<|> (Named
                       '("iput", LegalholdConfig)
                       (Description ""
                        :> (Summary "Put config for legalhold"
                            :> (CanThrow ('MissingPermission 'Nothing)
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> (CanThrow TeamFeatureError
                                            :> (CanThrowMany
                                                  '[ 'ActionDenied 'RemoveConversationMember,
                                                     'CannotEnableLegalHoldServiceLargeTeam,
                                                     'LegalHoldNotEnabled,
                                                     'LegalHoldDisableUnimplemented,
                                                     'LegalHoldServiceNotRegistered,
                                                     'UserLegalHoldIllegalOperation,
                                                     'LegalHoldCouldNotBlockConnections]
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("legalhold"
                                                                :> (ReqBody
                                                                      '[JSON]
                                                                      (Feature LegalholdConfig)
                                                                    :> Put
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            LegalholdConfig)))))))))))))
                     :<|> Named
                            '("ipatch", LegalholdConfig)
                            (Description ""
                             :> (Summary "Patch config for legalhold"
                                 :> (CanThrow ('MissingPermission 'Nothing)
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow TeamFeatureError
                                                 :> (CanThrowMany
                                                       '[ 'ActionDenied 'RemoveConversationMember,
                                                          'CannotEnableLegalHoldServiceLargeTeam,
                                                          'LegalHoldNotEnabled,
                                                          'LegalHoldDisableUnimplemented,
                                                          'LegalHoldServiceNotRegistered,
                                                          'UserLegalHoldIllegalOperation,
                                                          'LegalHoldCouldNotBlockConnections]
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("legalhold"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           (LockableFeaturePatch
                                                                              LegalholdConfig)
                                                                         :> Patch
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 LegalholdConfig)))))))))))))))
              :<|> ((Named
                       '("iget", SSOConfig)
                       (Description ""
                        :> (Summary "Get config for sso"
                            :> (CanThrow ('MissingPermission 'Nothing)
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("sso"
                                                        :> Get
                                                             '[JSON]
                                                             (LockableFeature SSOConfig))))))))))
                     :<|> (Named
                             '("iput", SSOConfig)
                             (Description ""
                              :> (Summary "Put config for sso"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> (CanThrow TeamFeatureError
                                                  :> (CanThrowMany '[]
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("sso"
                                                                      :> (ReqBody
                                                                            '[JSON]
                                                                            (Feature SSOConfig)
                                                                          :> Put
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  SSOConfig)))))))))))))
                           :<|> Named
                                  '("ipatch", SSOConfig)
                                  (Description ""
                                   :> (Summary "Patch config for sso"
                                       :> (CanThrow ('MissingPermission 'Nothing)
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany '[]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("sso"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (LockableFeaturePatch
                                                                                    SSOConfig)
                                                                               :> Patch
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       SSOConfig)))))))))))))))
                    :<|> ((Named
                             '("iget", SearchVisibilityAvailableConfig)
                             (Description ""
                              :> (Summary "Get config for searchVisibility"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("searchVisibility"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      SearchVisibilityAvailableConfig))))))))))
                           :<|> (Named
                                   '("iput", SearchVisibilityAvailableConfig)
                                   (Description ""
                                    :> (Summary "Put config for searchVisibility"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> (CanThrow TeamFeatureError
                                                        :> (CanThrowMany '[]
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("searchVisibility"
                                                                            :> (ReqBody
                                                                                  '[JSON]
                                                                                  (Feature
                                                                                     SearchVisibilityAvailableConfig)
                                                                                :> Put
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SearchVisibilityAvailableConfig)))))))))))))
                                 :<|> Named
                                        '("ipatch", SearchVisibilityAvailableConfig)
                                        (Description ""
                                         :> (Summary "Patch config for searchVisibility"
                                             :> (CanThrow ('MissingPermission 'Nothing)
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("searchVisibility"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (LockableFeaturePatch
                                                                                          SearchVisibilityAvailableConfig)
                                                                                     :> Patch
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             SearchVisibilityAvailableConfig)))))))))))))))
                          :<|> ((Named
                                   '("iget", SearchVisibilityInboundConfig)
                                   (Description ""
                                    :> (Summary "Get config for searchVisibilityInbound"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("searchVisibilityInbound"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            SearchVisibilityInboundConfig))))))))))
                                 :<|> (Named
                                         '("iput", SearchVisibilityInboundConfig)
                                         (Description ""
                                          :> (Summary "Put config for searchVisibilityInbound"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow TeamFeatureError
                                                              :> (CanThrowMany '[]
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("searchVisibilityInbound"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        (Feature
                                                                                           SearchVisibilityInboundConfig)
                                                                                      :> Put
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              SearchVisibilityInboundConfig)))))))))))))
                                       :<|> Named
                                              '("ipatch", SearchVisibilityInboundConfig)
                                              (Description ""
                                               :> (Summary
                                                     "Patch config for searchVisibilityInbound"
                                                   :> (CanThrow ('MissingPermission 'Nothing)
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("searchVisibilityInbound"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (LockableFeaturePatch
                                                                                                SearchVisibilityInboundConfig)
                                                                                           :> Patch
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   SearchVisibilityInboundConfig)))))))))))))))
                                :<|> ((Named
                                         '("iget", ValidateSAMLEmailsConfig)
                                         (Description ""
                                          :> (Summary "Get config for validateSAMLemails"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("validateSAMLemails"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  ValidateSAMLEmailsConfig))))))))))
                                       :<|> (Named
                                               '("iput", ValidateSAMLEmailsConfig)
                                               (Description ""
                                                :> (Summary "Put config for validateSAMLemails"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> (CanThrowMany '[]
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("validateSAMLemails"
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              (Feature
                                                                                                 ValidateSAMLEmailsConfig)
                                                                                            :> Put
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    ValidateSAMLEmailsConfig)))))))))))))
                                             :<|> Named
                                                    '("ipatch", ValidateSAMLEmailsConfig)
                                                    (Description ""
                                                     :> (Summary
                                                           "Patch config for validateSAMLemails"
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("validateSAMLemails"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (LockableFeaturePatch
                                                                                                      ValidateSAMLEmailsConfig)
                                                                                                 :> Patch
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         ValidateSAMLEmailsConfig)))))))))))))))
                                      :<|> ((Named
                                               '("iget", DigitalSignaturesConfig)
                                               (Description ""
                                                :> (Summary "Get config for digitalSignatures"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("digitalSignatures"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        DigitalSignaturesConfig))))))))))
                                             :<|> (Named
                                                     '("iput", DigitalSignaturesConfig)
                                                     (Description ""
                                                      :> (Summary "Put config for digitalSignatures"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany '[]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("digitalSignatures"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (Feature
                                                                                                       DigitalSignaturesConfig)
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          DigitalSignaturesConfig)))))))))))))
                                                   :<|> Named
                                                          '("ipatch", DigitalSignaturesConfig)
                                                          (Description ""
                                                           :> (Summary
                                                                 "Patch config for digitalSignatures"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("digitalSignatures"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (LockableFeaturePatch
                                                                                                            DigitalSignaturesConfig)
                                                                                                       :> Patch
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               DigitalSignaturesConfig)))))))))))))))
                                            :<|> ((Named
                                                     '("iget", AppLockConfig)
                                                     (Description ""
                                                      :> (Summary "Get config for appLock"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("appLock"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              AppLockConfig))))))))))
                                                   :<|> (Named
                                                           '("iput", AppLockConfig)
                                                           (Description ""
                                                            :> (Summary "Put config for appLock"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("appLock"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             AppLockConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                AppLockConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch", AppLockConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Patch config for appLock"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("appLock"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  AppLockConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     AppLockConfig)))))))))))))))
                                                  :<|> ((Named
                                                           '("iget", FileSharingConfig)
                                                           (Description ""
                                                            :> (Summary "Get config for fileSharing"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("fileSharing"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    FileSharingConfig))))))))))
                                                         :<|> (Named
                                                                 '("iput", FileSharingConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Put config for fileSharing"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> (CanThrowMany
                                                                                            '[]
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("fileSharing"
                                                                                                          :> (ReqBody
                                                                                                                '[JSON]
                                                                                                                (Feature
                                                                                                                   FileSharingConfig)
                                                                                                              :> Put
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      FileSharingConfig)))))))))))))
                                                               :<|> Named
                                                                      '("ipatch", FileSharingConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Patch config for fileSharing"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("fileSharing"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeaturePatch
                                                                                                                        FileSharingConfig)
                                                                                                                   :> Patch
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           FileSharingConfig)))))))))))))))
                                                        :<|> (Named
                                                                '("iget", ClassifiedDomainsConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Get config for classifiedDomains"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("classifiedDomains"
                                                                                                 :> Get
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         ClassifiedDomainsConfig))))))))))
                                                              :<|> ((Named
                                                                       '("iget",
                                                                         ConferenceCallingConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for conferenceCalling"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("conferenceCalling"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                ConferenceCallingConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               ConferenceCallingConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for conferenceCalling"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("conferenceCalling"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               ConferenceCallingConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  ConferenceCallingConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    ConferenceCallingConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for conferenceCalling"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("conferenceCalling"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    ConferenceCallingConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       ConferenceCallingConfig)))))))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               SelfDeletingMessagesConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for selfDeletingMessages"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("selfDeletingMessages"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      SelfDeletingMessagesConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     SelfDeletingMessagesConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for selfDeletingMessages"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("selfDeletingMessages"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     SelfDeletingMessagesConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        SelfDeletingMessagesConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          SelfDeletingMessagesConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for selfDeletingMessages"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("selfDeletingMessages"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          SelfDeletingMessagesConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             SelfDeletingMessagesConfig)))))))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     GuestLinksConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for conversationGuestLinks"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("conversationGuestLinks"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            GuestLinksConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           GuestLinksConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for conversationGuestLinks"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("conversationGuestLinks"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           GuestLinksConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              GuestLinksConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                GuestLinksConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for conversationGuestLinks"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                GuestLinksConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   GuestLinksConfig)))))))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           SndFactorPasswordChallengeConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for sndFactorPasswordChallenge"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("sndFactorPasswordChallenge"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  SndFactorPasswordChallengeConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 SndFactorPasswordChallengeConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for sndFactorPasswordChallenge"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("sndFactorPasswordChallenge"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 SndFactorPasswordChallengeConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    SndFactorPasswordChallengeConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for sndFactorPasswordChallenge"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 MLSConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for mls"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mls"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        MLSConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       MLSConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for mls"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("mls"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       MLSConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          MLSConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            MLSConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for mls"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("mls"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            MLSConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               MLSConfig)))))))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             OutlookCalIntegrationConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for outlookCalIntegration"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("outlookCalIntegration"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    OutlookCalIntegrationConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   OutlookCalIntegrationConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for outlookCalIntegration"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("outlookCalIntegration"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   OutlookCalIntegrationConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      OutlookCalIntegrationConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        OutlookCalIntegrationConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for outlookCalIntegration"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("outlookCalIntegration"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        OutlookCalIntegrationConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           OutlookCalIntegrationConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   MlsE2EIdConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for mlsE2EId"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("mlsE2EId"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          MlsE2EIdConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         MlsE2EIdConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for mlsE2EId"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("mlsE2EId"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         MlsE2EIdConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MlsE2EIdConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              MlsE2EIdConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for mlsE2EId"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("mlsE2EId"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              MlsE2EIdConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 MlsE2EIdConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         MlsMigrationConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for mlsMigration"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("mlsMigration"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                MlsMigrationConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               MlsMigrationConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for mlsMigration"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("mlsMigration"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               MlsMigrationConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  MlsMigrationConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    MlsMigrationConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for mlsMigration"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("mlsMigration"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    MlsMigrationConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       MlsMigrationConfig)))))))))))))))
                                                                                                                    :<|> ((Named
                                                                                                                             '("iget",
                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                             (Description
                                                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for enforceFileDownloadLocation"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      EnforceFileDownloadLocationConfig))))))))))
                                                                                                                           :<|> (Named
                                                                                                                                   '("iput",
                                                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                                                   (Description
                                                                                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                    :> (Summary
                                                                                                                                          "Put config for enforceFileDownloadLocation"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("enforceFileDownloadLocation"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Feature
                                                                                                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                                                                                                :> Put
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                 :<|> Named
                                                                                                                                        '("ipatch",
                                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                                        (Description
                                                                                                                                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                         :> (Summary
                                                                                                                                               "Patch config for enforceFileDownloadLocation"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("enforceFileDownloadLocation"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                                                                                     :> Patch
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                          :<|> (Named
                                                                                                                                  '("iget",
                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Get config for limitedEventFanout"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("teams"
                                                                                                                                                       :> (Capture
                                                                                                                                                             "tid"
                                                                                                                                                             TeamId
                                                                                                                                                           :> ("features"
                                                                                                                                                               :> ("limitedEventFanout"
                                                                                                                                                                   :> Get
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           LimitedEventFanoutConfig))))))))))
                                                                                                                                :<|> (Named
                                                                                                                                        '("iput",
                                                                                                                                          LimitedEventFanoutConfig)
                                                                                                                                        (Description
                                                                                                                                           ""
                                                                                                                                         :> (Summary
                                                                                                                                               "Put config for limitedEventFanout"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('MissingPermission
                                                                                                                                                      'Nothing)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("limitedEventFanout"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (Feature
                                                                                                                                                                                          LimitedEventFanoutConfig)
                                                                                                                                                                                     :> Put
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             LimitedEventFanoutConfig)))))))))))))
                                                                                                                                      :<|> Named
                                                                                                                                             '("ipatch",
                                                                                                                                               LimitedEventFanoutConfig)
                                                                                                                                             (Description
                                                                                                                                                ""
                                                                                                                                              :> (Summary
                                                                                                                                                    "Patch config for limitedEventFanout"
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        ('MissingPermission
                                                                                                                                                           'Nothing)
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'NotATeamMember
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                'TeamNotFound
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    TeamFeatureError
                                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                                        '[]
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("limitedEventFanout"
                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            (LockableFeaturePatch
                                                                                                                                                                                               LimitedEventFanoutConfig)
                                                                                                                                                                                          :> Patch
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                                  LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
             :<|> (Named
                     '("ilock", FileSharingConfig)
                     (Summary "(Un-)lock fileSharing"
                      :> (Description ""
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("fileSharing"
                                                  :> (Capture "lockStatus" LockStatus
                                                      :> Put '[JSON] LockStatusResponse)))))))))
                   :<|> (Named
                           '("ilock", ConferenceCallingConfig)
                           (Summary "(Un-)lock conferenceCalling"
                            :> (Description ""
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("conferenceCalling"
                                                        :> (Capture "lockStatus" LockStatus
                                                            :> Put
                                                                 '[JSON] LockStatusResponse)))))))))
                         :<|> (Named
                                 '("ilock", SelfDeletingMessagesConfig)
                                 (Summary "(Un-)lock selfDeletingMessages"
                                  :> (Description ""
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("selfDeletingMessages"
                                                              :> (Capture "lockStatus" LockStatus
                                                                  :> Put
                                                                       '[JSON]
                                                                       LockStatusResponse)))))))))
                               :<|> (Named
                                       '("ilock", GuestLinksConfig)
                                       (Summary "(Un-)lock conversationGuestLinks"
                                        :> (Description ""
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("conversationGuestLinks"
                                                                    :> (Capture
                                                                          "lockStatus" LockStatus
                                                                        :> Put
                                                                             '[JSON]
                                                                             LockStatusResponse)))))))))
                                     :<|> (Named
                                             '("ilock", SndFactorPasswordChallengeConfig)
                                             (Summary "(Un-)lock sndFactorPasswordChallenge"
                                              :> (Description ""
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("sndFactorPasswordChallenge"
                                                                          :> (Capture
                                                                                "lockStatus"
                                                                                LockStatus
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   LockStatusResponse)))))))))
                                           :<|> (Named
                                                   '("ilock", MLSConfig)
                                                   (Summary "(Un-)lock mls"
                                                    :> (Description ""
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("mls"
                                                                                :> (Capture
                                                                                      "lockStatus"
                                                                                      LockStatus
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         LockStatusResponse)))))))))
                                                 :<|> (Named
                                                         '("ilock", OutlookCalIntegrationConfig)
                                                         (Summary "(Un-)lock outlookCalIntegration"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("outlookCalIntegration"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock", MlsE2EIdConfig)
                                                               (Summary "(Un-)lock mlsE2EId"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mlsE2EId"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock", MlsMigrationConfig)
                                                                     (Summary
                                                                        "(Un-)lock mlsMigration"
                                                                      :> (Description ""
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mlsMigration"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("ilock",
                                                                             EnforceFileDownloadLocationConfig)
                                                                           (Summary
                                                                              "(Un-)lock enforceFileDownloadLocation"
                                                                            :> (Description
                                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                        :> (Capture
                                                                                                              "lockStatus"
                                                                                                              LockStatus
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 LockStatusResponse)))))))))
                                                                         :<|> (Named
                                                                                 '("igetmulti",
                                                                                   SearchVisibilityInboundConfig)
                                                                                 (Summary
                                                                                    "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                  :> ("features-multi-teams"
                                                                                      :> ("searchVisibilityInbound"
                                                                                          :> (ReqBody
                                                                                                '[JSON]
                                                                                                TeamFeatureNoConfigMultiRequest
                                                                                              :> Post
                                                                                                   '[JSON]
                                                                                                   (TeamFeatureNoConfigMultiResponse
                                                                                                      SearchVisibilityInboundConfig)))))
                                                                               :<|> Named
                                                                                      "feature-configs-internal"
                                                                                      (Summary
                                                                                         "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                       :> ("feature-configs"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (QueryParam'
                                                                                                             '[Optional,
                                                                                                               Strict,
                                                                                                               Description
                                                                                                                 "Optional user id"]
                                                                                                             "user_id"
                                                                                                             UserId
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                AllTeamFeatures))))))))))))))))))
            :<|> (IFederationAPI :<|> (IConversationAPI :<|> IEJPDAPI))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (((Named
       '("iget", LegalholdConfig)
       (Description ""
        :> (Summary "Get config for legalhold"
            :> (CanThrow ('MissingPermission 'Nothing)
                :> (CanThrow 'NotATeamMember
                    :> (CanThrow 'TeamNotFound
                        :> ("teams"
                            :> (Capture "tid" TeamId
                                :> ("features"
                                    :> ("legalhold"
                                        :> Get '[JSON] (LockableFeature LegalholdConfig))))))))))
     :<|> (Named
             '("iput", LegalholdConfig)
             (Description ""
              :> (Summary "Put config for legalhold"
                  :> (CanThrow ('MissingPermission 'Nothing)
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> (CanThrow TeamFeatureError
                                  :> (CanThrowMany
                                        '[ 'ActionDenied 'RemoveConversationMember,
                                           'CannotEnableLegalHoldServiceLargeTeam,
                                           'LegalHoldNotEnabled, 'LegalHoldDisableUnimplemented,
                                           'LegalHoldServiceNotRegistered,
                                           'UserLegalHoldIllegalOperation,
                                           'LegalHoldCouldNotBlockConnections]
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("legalhold"
                                                      :> (ReqBody '[JSON] (Feature LegalholdConfig)
                                                          :> Put
                                                               '[JSON]
                                                               (LockableFeature
                                                                  LegalholdConfig)))))))))))))
           :<|> Named
                  '("ipatch", LegalholdConfig)
                  (Description ""
                   :> (Summary "Patch config for legalhold"
                       :> (CanThrow ('MissingPermission 'Nothing)
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany
                                             '[ 'ActionDenied 'RemoveConversationMember,
                                                'CannotEnableLegalHoldServiceLargeTeam,
                                                'LegalHoldNotEnabled,
                                                'LegalHoldDisableUnimplemented,
                                                'LegalHoldServiceNotRegistered,
                                                'UserLegalHoldIllegalOperation,
                                                'LegalHoldCouldNotBlockConnections]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("legalhold"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (LockableFeaturePatch
                                                                    LegalholdConfig)
                                                               :> Patch
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       LegalholdConfig)))))))))))))))
    :<|> ((Named
             '("iget", SSOConfig)
             (Description ""
              :> (Summary "Get config for sso"
                  :> (CanThrow ('MissingPermission 'Nothing)
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("sso"
                                              :> Get '[JSON] (LockableFeature SSOConfig))))))))))
           :<|> (Named
                   '("iput", SSOConfig)
                   (Description ""
                    :> (Summary "Put config for sso"
                        :> (CanThrow ('MissingPermission 'Nothing)
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> (CanThrow TeamFeatureError
                                        :> (CanThrowMany '[]
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("sso"
                                                            :> (ReqBody '[JSON] (Feature SSOConfig)
                                                                :> Put
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        SSOConfig)))))))))))))
                 :<|> Named
                        '("ipatch", SSOConfig)
                        (Description ""
                         :> (Summary "Patch config for sso"
                             :> (CanThrow ('MissingPermission 'Nothing)
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("sso"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (LockableFeaturePatch
                                                                          SSOConfig)
                                                                     :> Patch
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             SSOConfig)))))))))))))))
          :<|> ((Named
                   '("iget", SearchVisibilityAvailableConfig)
                   (Description ""
                    :> (Summary "Get config for searchVisibility"
                        :> (CanThrow ('MissingPermission 'Nothing)
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("searchVisibility"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            SearchVisibilityAvailableConfig))))))))))
                 :<|> (Named
                         '("iput", SearchVisibilityAvailableConfig)
                         (Description ""
                          :> (Summary "Put config for searchVisibility"
                              :> (CanThrow ('MissingPermission 'Nothing)
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> (CanThrow TeamFeatureError
                                              :> (CanThrowMany '[]
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("searchVisibility"
                                                                  :> (ReqBody
                                                                        '[JSON]
                                                                        (Feature
                                                                           SearchVisibilityAvailableConfig)
                                                                      :> Put
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              SearchVisibilityAvailableConfig)))))))))))))
                       :<|> Named
                              '("ipatch", SearchVisibilityAvailableConfig)
                              (Description ""
                               :> (Summary "Patch config for searchVisibility"
                                   :> (CanThrow ('MissingPermission 'Nothing)
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("searchVisibility"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (LockableFeaturePatch
                                                                                SearchVisibilityAvailableConfig)
                                                                           :> Patch
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   SearchVisibilityAvailableConfig)))))))))))))))
                :<|> ((Named
                         '("iget", SearchVisibilityInboundConfig)
                         (Description ""
                          :> (Summary "Get config for searchVisibilityInbound"
                              :> (CanThrow ('MissingPermission 'Nothing)
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("searchVisibilityInbound"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  SearchVisibilityInboundConfig))))))))))
                       :<|> (Named
                               '("iput", SearchVisibilityInboundConfig)
                               (Description ""
                                :> (Summary "Put config for searchVisibilityInbound"
                                    :> (CanThrow ('MissingPermission 'Nothing)
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> (CanThrow TeamFeatureError
                                                    :> (CanThrowMany '[]
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("searchVisibilityInbound"
                                                                        :> (ReqBody
                                                                              '[JSON]
                                                                              (Feature
                                                                                 SearchVisibilityInboundConfig)
                                                                            :> Put
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    SearchVisibilityInboundConfig)))))))))))))
                             :<|> Named
                                    '("ipatch", SearchVisibilityInboundConfig)
                                    (Description ""
                                     :> (Summary "Patch config for searchVisibilityInbound"
                                         :> (CanThrow ('MissingPermission 'Nothing)
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("searchVisibilityInbound"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (LockableFeaturePatch
                                                                                      SearchVisibilityInboundConfig)
                                                                                 :> Patch
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         SearchVisibilityInboundConfig)))))))))))))))
                      :<|> ((Named
                               '("iget", ValidateSAMLEmailsConfig)
                               (Description ""
                                :> (Summary "Get config for validateSAMLemails"
                                    :> (CanThrow ('MissingPermission 'Nothing)
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("validateSAMLemails"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        ValidateSAMLEmailsConfig))))))))))
                             :<|> (Named
                                     '("iput", ValidateSAMLEmailsConfig)
                                     (Description ""
                                      :> (Summary "Put config for validateSAMLemails"
                                          :> (CanThrow ('MissingPermission 'Nothing)
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> (CanThrow TeamFeatureError
                                                          :> (CanThrowMany '[]
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("validateSAMLemails"
                                                                              :> (ReqBody
                                                                                    '[JSON]
                                                                                    (Feature
                                                                                       ValidateSAMLEmailsConfig)
                                                                                  :> Put
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          ValidateSAMLEmailsConfig)))))))))))))
                                   :<|> Named
                                          '("ipatch", ValidateSAMLEmailsConfig)
                                          (Description ""
                                           :> (Summary "Patch config for validateSAMLemails"
                                               :> (CanThrow ('MissingPermission 'Nothing)
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("validateSAMLemails"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (LockableFeaturePatch
                                                                                            ValidateSAMLEmailsConfig)
                                                                                       :> Patch
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               ValidateSAMLEmailsConfig)))))))))))))))
                            :<|> ((Named
                                     '("iget", DigitalSignaturesConfig)
                                     (Description ""
                                      :> (Summary "Get config for digitalSignatures"
                                          :> (CanThrow ('MissingPermission 'Nothing)
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("digitalSignatures"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              DigitalSignaturesConfig))))))))))
                                   :<|> (Named
                                           '("iput", DigitalSignaturesConfig)
                                           (Description ""
                                            :> (Summary "Put config for digitalSignatures"
                                                :> (CanThrow ('MissingPermission 'Nothing)
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> (CanThrow TeamFeatureError
                                                                :> (CanThrowMany '[]
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("digitalSignatures"
                                                                                    :> (ReqBody
                                                                                          '[JSON]
                                                                                          (Feature
                                                                                             DigitalSignaturesConfig)
                                                                                        :> Put
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                DigitalSignaturesConfig)))))))))))))
                                         :<|> Named
                                                '("ipatch", DigitalSignaturesConfig)
                                                (Description ""
                                                 :> (Summary "Patch config for digitalSignatures"
                                                     :> (CanThrow ('MissingPermission 'Nothing)
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("digitalSignatures"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (LockableFeaturePatch
                                                                                                  DigitalSignaturesConfig)
                                                                                             :> Patch
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     DigitalSignaturesConfig)))))))))))))))
                                  :<|> ((Named
                                           '("iget", AppLockConfig)
                                           (Description ""
                                            :> (Summary "Get config for appLock"
                                                :> (CanThrow ('MissingPermission 'Nothing)
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("appLock"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    AppLockConfig))))))))))
                                         :<|> (Named
                                                 '("iput", AppLockConfig)
                                                 (Description ""
                                                  :> (Summary "Put config for appLock"
                                                      :> (CanThrow ('MissingPermission 'Nothing)
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> (CanThrow TeamFeatureError
                                                                      :> (CanThrowMany '[]
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("appLock"
                                                                                          :> (ReqBody
                                                                                                '[JSON]
                                                                                                (Feature
                                                                                                   AppLockConfig)
                                                                                              :> Put
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      AppLockConfig)))))))))))))
                                               :<|> Named
                                                      '("ipatch", AppLockConfig)
                                                      (Description ""
                                                       :> (Summary "Patch config for appLock"
                                                           :> (CanThrow
                                                                 ('MissingPermission 'Nothing)
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("appLock"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (LockableFeaturePatch
                                                                                                        AppLockConfig)
                                                                                                   :> Patch
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           AppLockConfig)))))))))))))))
                                        :<|> ((Named
                                                 '("iget", FileSharingConfig)
                                                 (Description ""
                                                  :> (Summary "Get config for fileSharing"
                                                      :> (CanThrow ('MissingPermission 'Nothing)
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("fileSharing"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          FileSharingConfig))))))))))
                                               :<|> (Named
                                                       '("iput", FileSharingConfig)
                                                       (Description ""
                                                        :> (Summary "Put config for fileSharing"
                                                            :> (CanThrow
                                                                  ('MissingPermission 'Nothing)
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> (CanThrow
                                                                              TeamFeatureError
                                                                            :> (CanThrowMany '[]
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("fileSharing"
                                                                                                :> (ReqBody
                                                                                                      '[JSON]
                                                                                                      (Feature
                                                                                                         FileSharingConfig)
                                                                                                    :> Put
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            FileSharingConfig)))))))))))))
                                                     :<|> Named
                                                            '("ipatch", FileSharingConfig)
                                                            (Description ""
                                                             :> (Summary
                                                                   "Patch config for fileSharing"
                                                                 :> (CanThrow
                                                                       ('MissingPermission 'Nothing)
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("fileSharing"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (LockableFeaturePatch
                                                                                                              FileSharingConfig)
                                                                                                         :> Patch
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 FileSharingConfig)))))))))))))))
                                              :<|> (Named
                                                      '("iget", ClassifiedDomainsConfig)
                                                      (Description ""
                                                       :> (Summary
                                                             "Get config for classifiedDomains"
                                                           :> (CanThrow
                                                                 ('MissingPermission 'Nothing)
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("classifiedDomains"
                                                                                       :> Get
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               ClassifiedDomainsConfig))))))))))
                                                    :<|> ((Named
                                                             '("iget", ConferenceCallingConfig)
                                                             (Description ""
                                                              :> (Summary
                                                                    "Get config for conferenceCalling"
                                                                  :> (CanThrow
                                                                        ('MissingPermission
                                                                           'Nothing)
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("conferenceCalling"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      ConferenceCallingConfig))))))))))
                                                           :<|> (Named
                                                                   '("iput",
                                                                     ConferenceCallingConfig)
                                                                   (Description ""
                                                                    :> (Summary
                                                                          "Put config for conferenceCalling"
                                                                        :> (CanThrow
                                                                              ('MissingPermission
                                                                                 'Nothing)
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> (CanThrow
                                                                                          TeamFeatureError
                                                                                        :> (CanThrowMany
                                                                                              '[]
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("conferenceCalling"
                                                                                                            :> (ReqBody
                                                                                                                  '[JSON]
                                                                                                                  (Feature
                                                                                                                     ConferenceCallingConfig)
                                                                                                                :> Put
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        ConferenceCallingConfig)))))))))))))
                                                                 :<|> Named
                                                                        '("ipatch",
                                                                          ConferenceCallingConfig)
                                                                        (Description ""
                                                                         :> (Summary
                                                                               "Patch config for conferenceCalling"
                                                                             :> (CanThrow
                                                                                   ('MissingPermission
                                                                                      'Nothing)
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("conferenceCalling"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeaturePatch
                                                                                                                          ConferenceCallingConfig)
                                                                                                                     :> Patch
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             ConferenceCallingConfig)))))))))))))))
                                                          :<|> ((Named
                                                                   '("iget",
                                                                     SelfDeletingMessagesConfig)
                                                                   (Description ""
                                                                    :> (Summary
                                                                          "Get config for selfDeletingMessages"
                                                                        :> (CanThrow
                                                                              ('MissingPermission
                                                                                 'Nothing)
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("selfDeletingMessages"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            SelfDeletingMessagesConfig))))))))))
                                                                 :<|> (Named
                                                                         '("iput",
                                                                           SelfDeletingMessagesConfig)
                                                                         (Description ""
                                                                          :> (Summary
                                                                                "Put config for selfDeletingMessages"
                                                                              :> (CanThrow
                                                                                    ('MissingPermission
                                                                                       'Nothing)
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> (CanThrow
                                                                                                TeamFeatureError
                                                                                              :> (CanThrowMany
                                                                                                    '[]
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("selfDeletingMessages"
                                                                                                                  :> (ReqBody
                                                                                                                        '[JSON]
                                                                                                                        (Feature
                                                                                                                           SelfDeletingMessagesConfig)
                                                                                                                      :> Put
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              SelfDeletingMessagesConfig)))))))))))))
                                                                       :<|> Named
                                                                              '("ipatch",
                                                                                SelfDeletingMessagesConfig)
                                                                              (Description ""
                                                                               :> (Summary
                                                                                     "Patch config for selfDeletingMessages"
                                                                                   :> (CanThrow
                                                                                         ('MissingPermission
                                                                                            'Nothing)
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("selfDeletingMessages"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeaturePatch
                                                                                                                                SelfDeletingMessagesConfig)
                                                                                                                           :> Patch
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   SelfDeletingMessagesConfig)))))))))))))))
                                                                :<|> ((Named
                                                                         '("iget", GuestLinksConfig)
                                                                         (Description ""
                                                                          :> (Summary
                                                                                "Get config for conversationGuestLinks"
                                                                              :> (CanThrow
                                                                                    ('MissingPermission
                                                                                       'Nothing)
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("conversationGuestLinks"
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  GuestLinksConfig))))))))))
                                                                       :<|> (Named
                                                                               '("iput",
                                                                                 GuestLinksConfig)
                                                                               (Description ""
                                                                                :> (Summary
                                                                                      "Put config for conversationGuestLinks"
                                                                                    :> (CanThrow
                                                                                          ('MissingPermission
                                                                                             'Nothing)
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> (CanThrow
                                                                                                      TeamFeatureError
                                                                                                    :> (CanThrowMany
                                                                                                          '[]
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("conversationGuestLinks"
                                                                                                                        :> (ReqBody
                                                                                                                              '[JSON]
                                                                                                                              (Feature
                                                                                                                                 GuestLinksConfig)
                                                                                                                            :> Put
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeature
                                                                                                                                    GuestLinksConfig)))))))))))))
                                                                             :<|> Named
                                                                                    '("ipatch",
                                                                                      GuestLinksConfig)
                                                                                    (Description ""
                                                                                     :> (Summary
                                                                                           "Patch config for conversationGuestLinks"
                                                                                         :> (CanThrow
                                                                                               ('MissingPermission
                                                                                                  'Nothing)
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           TeamFeatureError
                                                                                                         :> (CanThrowMany
                                                                                                               '[]
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeaturePatch
                                                                                                                                      GuestLinksConfig)
                                                                                                                                 :> Patch
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         GuestLinksConfig)))))))))))))))
                                                                      :<|> ((Named
                                                                               '("iget",
                                                                                 SndFactorPasswordChallengeConfig)
                                                                               (Description ""
                                                                                :> (Summary
                                                                                      "Get config for sndFactorPasswordChallenge"
                                                                                    :> (CanThrow
                                                                                          ('MissingPermission
                                                                                             'Nothing)
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("sndFactorPasswordChallenge"
                                                                                                                :> Get
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        SndFactorPasswordChallengeConfig))))))))))
                                                                             :<|> (Named
                                                                                     '("iput",
                                                                                       SndFactorPasswordChallengeConfig)
                                                                                     (Description ""
                                                                                      :> (Summary
                                                                                            "Put config for sndFactorPasswordChallenge"
                                                                                          :> (CanThrow
                                                                                                ('MissingPermission
                                                                                                   'Nothing)
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> (CanThrow
                                                                                                            TeamFeatureError
                                                                                                          :> (CanThrowMany
                                                                                                                '[]
                                                                                                              :> ("teams"
                                                                                                                  :> (Capture
                                                                                                                        "tid"
                                                                                                                        TeamId
                                                                                                                      :> ("features"
                                                                                                                          :> ("sndFactorPasswordChallenge"
                                                                                                                              :> (ReqBody
                                                                                                                                    '[JSON]
                                                                                                                                    (Feature
                                                                                                                                       SndFactorPasswordChallengeConfig)
                                                                                                                                  :> Put
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeature
                                                                                                                                          SndFactorPasswordChallengeConfig)))))))))))))
                                                                                   :<|> Named
                                                                                          '("ipatch",
                                                                                            SndFactorPasswordChallengeConfig)
                                                                                          (Description
                                                                                             ""
                                                                                           :> (Summary
                                                                                                 "Patch config for sndFactorPasswordChallenge"
                                                                                               :> (CanThrow
                                                                                                     ('MissingPermission
                                                                                                        'Nothing)
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> (CanThrow
                                                                                                                 TeamFeatureError
                                                                                                               :> (CanThrowMany
                                                                                                                     '[]
                                                                                                                   :> ("teams"
                                                                                                                       :> (Capture
                                                                                                                             "tid"
                                                                                                                             TeamId
                                                                                                                           :> ("features"
                                                                                                                               :> ("sndFactorPasswordChallenge"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeaturePatch
                                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                                       :> Patch
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               SndFactorPasswordChallengeConfig)))))))))))))))
                                                                            :<|> ((Named
                                                                                     '("iget",
                                                                                       MLSConfig)
                                                                                     (Description ""
                                                                                      :> (Summary
                                                                                            "Get config for mls"
                                                                                          :> (CanThrow
                                                                                                ('MissingPermission
                                                                                                   'Nothing)
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("mls"
                                                                                                                      :> Get
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              MLSConfig))))))))))
                                                                                   :<|> (Named
                                                                                           '("iput",
                                                                                             MLSConfig)
                                                                                           (Description
                                                                                              ""
                                                                                            :> (Summary
                                                                                                  "Put config for mls"
                                                                                                :> (CanThrow
                                                                                                      ('MissingPermission
                                                                                                         'Nothing)
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> (CanThrow
                                                                                                                  TeamFeatureError
                                                                                                                :> (CanThrowMany
                                                                                                                      '[]
                                                                                                                    :> ("teams"
                                                                                                                        :> (Capture
                                                                                                                              "tid"
                                                                                                                              TeamId
                                                                                                                            :> ("features"
                                                                                                                                :> ("mls"
                                                                                                                                    :> (ReqBody
                                                                                                                                          '[JSON]
                                                                                                                                          (Feature
                                                                                                                                             MLSConfig)
                                                                                                                                        :> Put
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeature
                                                                                                                                                MLSConfig)))))))))))))
                                                                                         :<|> Named
                                                                                                '("ipatch",
                                                                                                  MLSConfig)
                                                                                                (Description
                                                                                                   ""
                                                                                                 :> (Summary
                                                                                                       "Patch config for mls"
                                                                                                     :> (CanThrow
                                                                                                           ('MissingPermission
                                                                                                              'Nothing)
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       TeamFeatureError
                                                                                                                     :> (CanThrowMany
                                                                                                                           '[]
                                                                                                                         :> ("teams"
                                                                                                                             :> (Capture
                                                                                                                                   "tid"
                                                                                                                                   TeamId
                                                                                                                                 :> ("features"
                                                                                                                                     :> ("mls"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                  MLSConfig)
                                                                                                                                             :> Patch
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     MLSConfig)))))))))))))))
                                                                                  :<|> ((Named
                                                                                           '("iget",
                                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                                           (Description
                                                                                              ""
                                                                                            :> (Summary
                                                                                                  "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                :> (CanThrow
                                                                                                      ('MissingPermission
                                                                                                         'Nothing)
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                            :> Get
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeature
                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                         :<|> (Named
                                                                                                 '("iput",
                                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                                 (Description
                                                                                                    ""
                                                                                                  :> (Summary
                                                                                                        "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                      :> (CanThrow
                                                                                                            ('MissingPermission
                                                                                                               'Nothing)
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> (CanThrow
                                                                                                                        TeamFeatureError
                                                                                                                      :> (CanThrowMany
                                                                                                                            '[]
                                                                                                                          :> ("teams"
                                                                                                                              :> (Capture
                                                                                                                                    "tid"
                                                                                                                                    TeamId
                                                                                                                                  :> ("features"
                                                                                                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                          :> (ReqBody
                                                                                                                                                '[JSON]
                                                                                                                                                (Feature
                                                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                              :> Put
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeature
                                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                               :<|> Named
                                                                                                      '("ipatch",
                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                      (Description
                                                                                                         ""
                                                                                                       :> (Summary
                                                                                                             "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                           :> (CanThrow
                                                                                                                 ('MissingPermission
                                                                                                                    'Nothing)
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             TeamFeatureError
                                                                                                                           :> (CanThrowMany
                                                                                                                                 '[]
                                                                                                                               :> ("teams"
                                                                                                                                   :> (Capture
                                                                                                                                         "tid"
                                                                                                                                         TeamId
                                                                                                                                       :> ("features"
                                                                                                                                           :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                   :> Patch
                                                                                                                                                        '[JSON]
                                                                                                                                                        (LockableFeature
                                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                        :<|> ((Named
                                                                                                 '("iget",
                                                                                                   OutlookCalIntegrationConfig)
                                                                                                 (Description
                                                                                                    ""
                                                                                                  :> (Summary
                                                                                                        "Get config for outlookCalIntegration"
                                                                                                      :> (CanThrow
                                                                                                            ('MissingPermission
                                                                                                               'Nothing)
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("outlookCalIntegration"
                                                                                                                                  :> Get
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeature
                                                                                                                                          OutlookCalIntegrationConfig))))))))))
                                                                                               :<|> (Named
                                                                                                       '("iput",
                                                                                                         OutlookCalIntegrationConfig)
                                                                                                       (Description
                                                                                                          ""
                                                                                                        :> (Summary
                                                                                                              "Put config for outlookCalIntegration"
                                                                                                            :> (CanThrow
                                                                                                                  ('MissingPermission
                                                                                                                     'Nothing)
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          'TeamNotFound
                                                                                                                        :> (CanThrow
                                                                                                                              TeamFeatureError
                                                                                                                            :> (CanThrowMany
                                                                                                                                  '[]
                                                                                                                                :> ("teams"
                                                                                                                                    :> (Capture
                                                                                                                                          "tid"
                                                                                                                                          TeamId
                                                                                                                                        :> ("features"
                                                                                                                                            :> ("outlookCalIntegration"
                                                                                                                                                :> (ReqBody
                                                                                                                                                      '[JSON]
                                                                                                                                                      (Feature
                                                                                                                                                         OutlookCalIntegrationConfig)
                                                                                                                                                    :> Put
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeature
                                                                                                                                                            OutlookCalIntegrationConfig)))))))))))))
                                                                                                     :<|> Named
                                                                                                            '("ipatch",
                                                                                                              OutlookCalIntegrationConfig)
                                                                                                            (Description
                                                                                                               ""
                                                                                                             :> (Summary
                                                                                                                   "Patch config for outlookCalIntegration"
                                                                                                                 :> (CanThrow
                                                                                                                       ('MissingPermission
                                                                                                                          'Nothing)
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   TeamFeatureError
                                                                                                                                 :> (CanThrowMany
                                                                                                                                       '[]
                                                                                                                                     :> ("teams"
                                                                                                                                         :> (Capture
                                                                                                                                               "tid"
                                                                                                                                               TeamId
                                                                                                                                             :> ("features"
                                                                                                                                                 :> ("outlookCalIntegration"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                              OutlookCalIntegrationConfig)
                                                                                                                                                         :> Patch
                                                                                                                                                              '[JSON]
                                                                                                                                                              (LockableFeature
                                                                                                                                                                 OutlookCalIntegrationConfig)))))))))))))))
                                                                                              :<|> ((Named
                                                                                                       '("iget",
                                                                                                         MlsE2EIdConfig)
                                                                                                       (Description
                                                                                                          ""
                                                                                                        :> (Summary
                                                                                                              "Get config for mlsE2EId"
                                                                                                            :> (CanThrow
                                                                                                                  ('MissingPermission
                                                                                                                     'Nothing)
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          'TeamNotFound
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("mlsE2EId"
                                                                                                                                        :> Get
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeature
                                                                                                                                                MlsE2EIdConfig))))))))))
                                                                                                     :<|> (Named
                                                                                                             '("iput",
                                                                                                               MlsE2EIdConfig)
                                                                                                             (Description
                                                                                                                ""
                                                                                                              :> (Summary
                                                                                                                    "Put config for mlsE2EId"
                                                                                                                  :> (CanThrow
                                                                                                                        ('MissingPermission
                                                                                                                           'Nothing)
                                                                                                                      :> (CanThrow
                                                                                                                            'NotATeamMember
                                                                                                                          :> (CanThrow
                                                                                                                                'TeamNotFound
                                                                                                                              :> (CanThrow
                                                                                                                                    TeamFeatureError
                                                                                                                                  :> (CanThrowMany
                                                                                                                                        '[]
                                                                                                                                      :> ("teams"
                                                                                                                                          :> (Capture
                                                                                                                                                "tid"
                                                                                                                                                TeamId
                                                                                                                                              :> ("features"
                                                                                                                                                  :> ("mlsE2EId"
                                                                                                                                                      :> (ReqBody
                                                                                                                                                            '[JSON]
                                                                                                                                                            (Feature
                                                                                                                                                               MlsE2EIdConfig)
                                                                                                                                                          :> Put
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeature
                                                                                                                                                                  MlsE2EIdConfig)))))))))))))
                                                                                                           :<|> Named
                                                                                                                  '("ipatch",
                                                                                                                    MlsE2EIdConfig)
                                                                                                                  (Description
                                                                                                                     ""
                                                                                                                   :> (Summary
                                                                                                                         "Patch config for mlsE2EId"
                                                                                                                       :> (CanThrow
                                                                                                                             ('MissingPermission
                                                                                                                                'Nothing)
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'TeamNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         TeamFeatureError
                                                                                                                                       :> (CanThrowMany
                                                                                                                                             '[]
                                                                                                                                           :> ("teams"
                                                                                                                                               :> (Capture
                                                                                                                                                     "tid"
                                                                                                                                                     TeamId
                                                                                                                                                   :> ("features"
                                                                                                                                                       :> ("mlsE2EId"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                    MlsE2EIdConfig)
                                                                                                                                                               :> Patch
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (LockableFeature
                                                                                                                                                                       MlsE2EIdConfig)))))))))))))))
                                                                                                    :<|> ((Named
                                                                                                             '("iget",
                                                                                                               MlsMigrationConfig)
                                                                                                             (Description
                                                                                                                ""
                                                                                                              :> (Summary
                                                                                                                    "Get config for mlsMigration"
                                                                                                                  :> (CanThrow
                                                                                                                        ('MissingPermission
                                                                                                                           'Nothing)
                                                                                                                      :> (CanThrow
                                                                                                                            'NotATeamMember
                                                                                                                          :> (CanThrow
                                                                                                                                'TeamNotFound
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("mlsMigration"
                                                                                                                                              :> Get
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeature
                                                                                                                                                      MlsMigrationConfig))))))))))
                                                                                                           :<|> (Named
                                                                                                                   '("iput",
                                                                                                                     MlsMigrationConfig)
                                                                                                                   (Description
                                                                                                                      ""
                                                                                                                    :> (Summary
                                                                                                                          "Put config for mlsMigration"
                                                                                                                        :> (CanThrow
                                                                                                                              ('MissingPermission
                                                                                                                                 'Nothing)
                                                                                                                            :> (CanThrow
                                                                                                                                  'NotATeamMember
                                                                                                                                :> (CanThrow
                                                                                                                                      'TeamNotFound
                                                                                                                                    :> (CanThrow
                                                                                                                                          TeamFeatureError
                                                                                                                                        :> (CanThrowMany
                                                                                                                                              '[]
                                                                                                                                            :> ("teams"
                                                                                                                                                :> (Capture
                                                                                                                                                      "tid"
                                                                                                                                                      TeamId
                                                                                                                                                    :> ("features"
                                                                                                                                                        :> ("mlsMigration"
                                                                                                                                                            :> (ReqBody
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (Feature
                                                                                                                                                                     MlsMigrationConfig)
                                                                                                                                                                :> Put
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeature
                                                                                                                                                                        MlsMigrationConfig)))))))))))))
                                                                                                                 :<|> Named
                                                                                                                        '("ipatch",
                                                                                                                          MlsMigrationConfig)
                                                                                                                        (Description
                                                                                                                           ""
                                                                                                                         :> (Summary
                                                                                                                               "Patch config for mlsMigration"
                                                                                                                             :> (CanThrow
                                                                                                                                   ('MissingPermission
                                                                                                                                      'Nothing)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TeamNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               TeamFeatureError
                                                                                                                                             :> (CanThrowMany
                                                                                                                                                   '[]
                                                                                                                                                 :> ("teams"
                                                                                                                                                     :> (Capture
                                                                                                                                                           "tid"
                                                                                                                                                           TeamId
                                                                                                                                                         :> ("features"
                                                                                                                                                             :> ("mlsMigration"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                          MlsMigrationConfig)
                                                                                                                                                                     :> Patch
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          (LockableFeature
                                                                                                                                                                             MlsMigrationConfig)))))))))))))))
                                                                                                          :<|> ((Named
                                                                                                                   '("iget",
                                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                                   (Description
                                                                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                    :> (Summary
                                                                                                                          "Get config for enforceFileDownloadLocation"
                                                                                                                        :> (CanThrow
                                                                                                                              ('MissingPermission
                                                                                                                                 'Nothing)
                                                                                                                            :> (CanThrow
                                                                                                                                  'NotATeamMember
                                                                                                                                :> (CanThrow
                                                                                                                                      'TeamNotFound
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                                                    :> Get
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeature
                                                                                                                                                            EnforceFileDownloadLocationConfig))))))))))
                                                                                                                 :<|> (Named
                                                                                                                         '("iput",
                                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                                         (Description
                                                                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                          :> (Summary
                                                                                                                                "Put config for enforceFileDownloadLocation"
                                                                                                                              :> (CanThrow
                                                                                                                                    ('MissingPermission
                                                                                                                                       'Nothing)
                                                                                                                                  :> (CanThrow
                                                                                                                                        'NotATeamMember
                                                                                                                                      :> (CanThrow
                                                                                                                                            'TeamNotFound
                                                                                                                                          :> (CanThrow
                                                                                                                                                TeamFeatureError
                                                                                                                                              :> (CanThrowMany
                                                                                                                                                    '[]
                                                                                                                                                  :> ("teams"
                                                                                                                                                      :> (Capture
                                                                                                                                                            "tid"
                                                                                                                                                            TeamId
                                                                                                                                                          :> ("features"
                                                                                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (Feature
                                                                                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                                                                                      :> Put
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeature
                                                                                                                                                                              EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                       :<|> Named
                                                                                                                              '("ipatch",
                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                              (Description
                                                                                                                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                               :> (Summary
                                                                                                                                     "Patch config for enforceFileDownloadLocation"
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('MissingPermission
                                                                                                                                            'Nothing)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'TeamNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     TeamFeatureError
                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                         '[]
                                                                                                                                                       :> ("teams"
                                                                                                                                                           :> (Capture
                                                                                                                                                                 "tid"
                                                                                                                                                                 TeamId
                                                                                                                                                               :> ("features"
                                                                                                                                                                   :> ("enforceFileDownloadLocation"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                                                                           :> Patch
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                   EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                :<|> (Named
                                                                                                                        '("iget",
                                                                                                                          LimitedEventFanoutConfig)
                                                                                                                        (Description
                                                                                                                           ""
                                                                                                                         :> (Summary
                                                                                                                               "Get config for limitedEventFanout"
                                                                                                                             :> (CanThrow
                                                                                                                                   ('MissingPermission
                                                                                                                                      'Nothing)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TeamNotFound
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("limitedEventFanout"
                                                                                                                                                         :> Get
                                                                                                                                                              '[JSON]
                                                                                                                                                              (LockableFeature
                                                                                                                                                                 LimitedEventFanoutConfig))))))))))
                                                                                                                      :<|> (Named
                                                                                                                              '("iput",
                                                                                                                                LimitedEventFanoutConfig)
                                                                                                                              (Description
                                                                                                                                 ""
                                                                                                                               :> (Summary
                                                                                                                                     "Put config for limitedEventFanout"
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('MissingPermission
                                                                                                                                            'Nothing)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'TeamNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     TeamFeatureError
                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                         '[]
                                                                                                                                                       :> ("teams"
                                                                                                                                                           :> (Capture
                                                                                                                                                                 "tid"
                                                                                                                                                                 TeamId
                                                                                                                                                               :> ("features"
                                                                                                                                                                   :> ("limitedEventFanout"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             (Feature
                                                                                                                                                                                LimitedEventFanoutConfig)
                                                                                                                                                                           :> Put
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                   LimitedEventFanoutConfig)))))))))))))
                                                                                                                            :<|> Named
                                                                                                                                   '("ipatch",
                                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Patch config for limitedEventFanout"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("limitedEventFanout"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeaturePatch
                                                                                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                                                                                :> Patch
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
   :<|> (Named
           '("ilock", FileSharingConfig)
           (Summary "(Un-)lock fileSharing"
            :> (Description ""
                :> (CanThrow 'NotATeamMember
                    :> (CanThrow 'TeamNotFound
                        :> ("teams"
                            :> (Capture "tid" TeamId
                                :> ("features"
                                    :> ("fileSharing"
                                        :> (Capture "lockStatus" LockStatus
                                            :> Put '[JSON] LockStatusResponse)))))))))
         :<|> (Named
                 '("ilock", ConferenceCallingConfig)
                 (Summary "(Un-)lock conferenceCalling"
                  :> (Description ""
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("conferenceCalling"
                                              :> (Capture "lockStatus" LockStatus
                                                  :> Put '[JSON] LockStatusResponse)))))))))
               :<|> (Named
                       '("ilock", SelfDeletingMessagesConfig)
                       (Summary "(Un-)lock selfDeletingMessages"
                        :> (Description ""
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("selfDeletingMessages"
                                                    :> (Capture "lockStatus" LockStatus
                                                        :> Put '[JSON] LockStatusResponse)))))))))
                     :<|> (Named
                             '("ilock", GuestLinksConfig)
                             (Summary "(Un-)lock conversationGuestLinks"
                              :> (Description ""
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("conversationGuestLinks"
                                                          :> (Capture "lockStatus" LockStatus
                                                              :> Put
                                                                   '[JSON]
                                                                   LockStatusResponse)))))))))
                           :<|> (Named
                                   '("ilock", SndFactorPasswordChallengeConfig)
                                   (Summary "(Un-)lock sndFactorPasswordChallenge"
                                    :> (Description ""
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("sndFactorPasswordChallenge"
                                                                :> (Capture "lockStatus" LockStatus
                                                                    :> Put
                                                                         '[JSON]
                                                                         LockStatusResponse)))))))))
                                 :<|> (Named
                                         '("ilock", MLSConfig)
                                         (Summary "(Un-)lock mls"
                                          :> (Description ""
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("mls"
                                                                      :> (Capture
                                                                            "lockStatus" LockStatus
                                                                          :> Put
                                                                               '[JSON]
                                                                               LockStatusResponse)))))))))
                                       :<|> (Named
                                               '("ilock", OutlookCalIntegrationConfig)
                                               (Summary "(Un-)lock outlookCalIntegration"
                                                :> (Description ""
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("outlookCalIntegration"
                                                                            :> (Capture
                                                                                  "lockStatus"
                                                                                  LockStatus
                                                                                :> Put
                                                                                     '[JSON]
                                                                                     LockStatusResponse)))))))))
                                             :<|> (Named
                                                     '("ilock", MlsE2EIdConfig)
                                                     (Summary "(Un-)lock mlsE2EId"
                                                      :> (Description ""
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("mlsE2EId"
                                                                                  :> (Capture
                                                                                        "lockStatus"
                                                                                        LockStatus
                                                                                      :> Put
                                                                                           '[JSON]
                                                                                           LockStatusResponse)))))))))
                                                   :<|> (Named
                                                           '("ilock", MlsMigrationConfig)
                                                           (Summary "(Un-)lock mlsMigration"
                                                            :> (Description ""
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("mlsMigration"
                                                                                        :> (Capture
                                                                                              "lockStatus"
                                                                                              LockStatus
                                                                                            :> Put
                                                                                                 '[JSON]
                                                                                                 LockStatusResponse)))))))))
                                                         :<|> (Named
                                                                 '("ilock",
                                                                   EnforceFileDownloadLocationConfig)
                                                                 (Summary
                                                                    "(Un-)lock enforceFileDownloadLocation"
                                                                  :> (Description
                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("enforceFileDownloadLocation"
                                                                                              :> (Capture
                                                                                                    "lockStatus"
                                                                                                    LockStatus
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       LockStatusResponse)))))))))
                                                               :<|> (Named
                                                                       '("igetmulti",
                                                                         SearchVisibilityInboundConfig)
                                                                       (Summary
                                                                          "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                        :> ("features-multi-teams"
                                                                            :> ("searchVisibilityInbound"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      TeamFeatureNoConfigMultiRequest
                                                                                    :> Post
                                                                                         '[JSON]
                                                                                         (TeamFeatureNoConfigMultiResponse
                                                                                            SearchVisibilityInboundConfig)))))
                                                                     :<|> Named
                                                                            "feature-configs-internal"
                                                                            (Summary
                                                                               "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                             :> ("feature-configs"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (QueryParam'
                                                                                                   '[Optional,
                                                                                                     Strict,
                                                                                                     Description
                                                                                                       "Optional user id"]
                                                                                                   "user_id"
                                                                                                   UserId
                                                                                                 :> Get
                                                                                                      '[JSON]
                                                                                                      AllTeamFeatures))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 IFeatureAPI GalleyEffects
featureAPI
      API
  (((Named
       '("iget", LegalholdConfig)
       (Description ""
        :> (Summary "Get config for legalhold"
            :> (CanThrow ('MissingPermission 'Nothing)
                :> (CanThrow 'NotATeamMember
                    :> (CanThrow 'TeamNotFound
                        :> ("teams"
                            :> (Capture "tid" TeamId
                                :> ("features"
                                    :> ("legalhold"
                                        :> Get '[JSON] (LockableFeature LegalholdConfig))))))))))
     :<|> (Named
             '("iput", LegalholdConfig)
             (Description ""
              :> (Summary "Put config for legalhold"
                  :> (CanThrow ('MissingPermission 'Nothing)
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> (CanThrow TeamFeatureError
                                  :> (CanThrowMany
                                        '[ 'ActionDenied 'RemoveConversationMember,
                                           'CannotEnableLegalHoldServiceLargeTeam,
                                           'LegalHoldNotEnabled, 'LegalHoldDisableUnimplemented,
                                           'LegalHoldServiceNotRegistered,
                                           'UserLegalHoldIllegalOperation,
                                           'LegalHoldCouldNotBlockConnections]
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("legalhold"
                                                      :> (ReqBody '[JSON] (Feature LegalholdConfig)
                                                          :> Put
                                                               '[JSON]
                                                               (LockableFeature
                                                                  LegalholdConfig)))))))))))))
           :<|> Named
                  '("ipatch", LegalholdConfig)
                  (Description ""
                   :> (Summary "Patch config for legalhold"
                       :> (CanThrow ('MissingPermission 'Nothing)
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany
                                             '[ 'ActionDenied 'RemoveConversationMember,
                                                'CannotEnableLegalHoldServiceLargeTeam,
                                                'LegalHoldNotEnabled,
                                                'LegalHoldDisableUnimplemented,
                                                'LegalHoldServiceNotRegistered,
                                                'UserLegalHoldIllegalOperation,
                                                'LegalHoldCouldNotBlockConnections]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("legalhold"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (LockableFeaturePatch
                                                                    LegalholdConfig)
                                                               :> Patch
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       LegalholdConfig)))))))))))))))
    :<|> ((Named
             '("iget", SSOConfig)
             (Description ""
              :> (Summary "Get config for sso"
                  :> (CanThrow ('MissingPermission 'Nothing)
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("sso"
                                              :> Get '[JSON] (LockableFeature SSOConfig))))))))))
           :<|> (Named
                   '("iput", SSOConfig)
                   (Description ""
                    :> (Summary "Put config for sso"
                        :> (CanThrow ('MissingPermission 'Nothing)
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> (CanThrow TeamFeatureError
                                        :> (CanThrowMany '[]
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("sso"
                                                            :> (ReqBody '[JSON] (Feature SSOConfig)
                                                                :> Put
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        SSOConfig)))))))))))))
                 :<|> Named
                        '("ipatch", SSOConfig)
                        (Description ""
                         :> (Summary "Patch config for sso"
                             :> (CanThrow ('MissingPermission 'Nothing)
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("sso"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (LockableFeaturePatch
                                                                          SSOConfig)
                                                                     :> Patch
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             SSOConfig)))))))))))))))
          :<|> ((Named
                   '("iget", SearchVisibilityAvailableConfig)
                   (Description ""
                    :> (Summary "Get config for searchVisibility"
                        :> (CanThrow ('MissingPermission 'Nothing)
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("searchVisibility"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            SearchVisibilityAvailableConfig))))))))))
                 :<|> (Named
                         '("iput", SearchVisibilityAvailableConfig)
                         (Description ""
                          :> (Summary "Put config for searchVisibility"
                              :> (CanThrow ('MissingPermission 'Nothing)
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> (CanThrow TeamFeatureError
                                              :> (CanThrowMany '[]
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("searchVisibility"
                                                                  :> (ReqBody
                                                                        '[JSON]
                                                                        (Feature
                                                                           SearchVisibilityAvailableConfig)
                                                                      :> Put
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              SearchVisibilityAvailableConfig)))))))))))))
                       :<|> Named
                              '("ipatch", SearchVisibilityAvailableConfig)
                              (Description ""
                               :> (Summary "Patch config for searchVisibility"
                                   :> (CanThrow ('MissingPermission 'Nothing)
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("searchVisibility"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (LockableFeaturePatch
                                                                                SearchVisibilityAvailableConfig)
                                                                           :> Patch
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   SearchVisibilityAvailableConfig)))))))))))))))
                :<|> ((Named
                         '("iget", SearchVisibilityInboundConfig)
                         (Description ""
                          :> (Summary "Get config for searchVisibilityInbound"
                              :> (CanThrow ('MissingPermission 'Nothing)
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("searchVisibilityInbound"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  SearchVisibilityInboundConfig))))))))))
                       :<|> (Named
                               '("iput", SearchVisibilityInboundConfig)
                               (Description ""
                                :> (Summary "Put config for searchVisibilityInbound"
                                    :> (CanThrow ('MissingPermission 'Nothing)
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> (CanThrow TeamFeatureError
                                                    :> (CanThrowMany '[]
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("searchVisibilityInbound"
                                                                        :> (ReqBody
                                                                              '[JSON]
                                                                              (Feature
                                                                                 SearchVisibilityInboundConfig)
                                                                            :> Put
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    SearchVisibilityInboundConfig)))))))))))))
                             :<|> Named
                                    '("ipatch", SearchVisibilityInboundConfig)
                                    (Description ""
                                     :> (Summary "Patch config for searchVisibilityInbound"
                                         :> (CanThrow ('MissingPermission 'Nothing)
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("searchVisibilityInbound"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (LockableFeaturePatch
                                                                                      SearchVisibilityInboundConfig)
                                                                                 :> Patch
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         SearchVisibilityInboundConfig)))))))))))))))
                      :<|> ((Named
                               '("iget", ValidateSAMLEmailsConfig)
                               (Description ""
                                :> (Summary "Get config for validateSAMLemails"
                                    :> (CanThrow ('MissingPermission 'Nothing)
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("validateSAMLemails"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        ValidateSAMLEmailsConfig))))))))))
                             :<|> (Named
                                     '("iput", ValidateSAMLEmailsConfig)
                                     (Description ""
                                      :> (Summary "Put config for validateSAMLemails"
                                          :> (CanThrow ('MissingPermission 'Nothing)
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> (CanThrow TeamFeatureError
                                                          :> (CanThrowMany '[]
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("validateSAMLemails"
                                                                              :> (ReqBody
                                                                                    '[JSON]
                                                                                    (Feature
                                                                                       ValidateSAMLEmailsConfig)
                                                                                  :> Put
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          ValidateSAMLEmailsConfig)))))))))))))
                                   :<|> Named
                                          '("ipatch", ValidateSAMLEmailsConfig)
                                          (Description ""
                                           :> (Summary "Patch config for validateSAMLemails"
                                               :> (CanThrow ('MissingPermission 'Nothing)
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("validateSAMLemails"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (LockableFeaturePatch
                                                                                            ValidateSAMLEmailsConfig)
                                                                                       :> Patch
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               ValidateSAMLEmailsConfig)))))))))))))))
                            :<|> ((Named
                                     '("iget", DigitalSignaturesConfig)
                                     (Description ""
                                      :> (Summary "Get config for digitalSignatures"
                                          :> (CanThrow ('MissingPermission 'Nothing)
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("digitalSignatures"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              DigitalSignaturesConfig))))))))))
                                   :<|> (Named
                                           '("iput", DigitalSignaturesConfig)
                                           (Description ""
                                            :> (Summary "Put config for digitalSignatures"
                                                :> (CanThrow ('MissingPermission 'Nothing)
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> (CanThrow TeamFeatureError
                                                                :> (CanThrowMany '[]
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("digitalSignatures"
                                                                                    :> (ReqBody
                                                                                          '[JSON]
                                                                                          (Feature
                                                                                             DigitalSignaturesConfig)
                                                                                        :> Put
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                DigitalSignaturesConfig)))))))))))))
                                         :<|> Named
                                                '("ipatch", DigitalSignaturesConfig)
                                                (Description ""
                                                 :> (Summary "Patch config for digitalSignatures"
                                                     :> (CanThrow ('MissingPermission 'Nothing)
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("digitalSignatures"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (LockableFeaturePatch
                                                                                                  DigitalSignaturesConfig)
                                                                                             :> Patch
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     DigitalSignaturesConfig)))))))))))))))
                                  :<|> ((Named
                                           '("iget", AppLockConfig)
                                           (Description ""
                                            :> (Summary "Get config for appLock"
                                                :> (CanThrow ('MissingPermission 'Nothing)
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("appLock"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    AppLockConfig))))))))))
                                         :<|> (Named
                                                 '("iput", AppLockConfig)
                                                 (Description ""
                                                  :> (Summary "Put config for appLock"
                                                      :> (CanThrow ('MissingPermission 'Nothing)
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> (CanThrow TeamFeatureError
                                                                      :> (CanThrowMany '[]
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("appLock"
                                                                                          :> (ReqBody
                                                                                                '[JSON]
                                                                                                (Feature
                                                                                                   AppLockConfig)
                                                                                              :> Put
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      AppLockConfig)))))))))))))
                                               :<|> Named
                                                      '("ipatch", AppLockConfig)
                                                      (Description ""
                                                       :> (Summary "Patch config for appLock"
                                                           :> (CanThrow
                                                                 ('MissingPermission 'Nothing)
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("appLock"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (LockableFeaturePatch
                                                                                                        AppLockConfig)
                                                                                                   :> Patch
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           AppLockConfig)))))))))))))))
                                        :<|> ((Named
                                                 '("iget", FileSharingConfig)
                                                 (Description ""
                                                  :> (Summary "Get config for fileSharing"
                                                      :> (CanThrow ('MissingPermission 'Nothing)
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("fileSharing"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          FileSharingConfig))))))))))
                                               :<|> (Named
                                                       '("iput", FileSharingConfig)
                                                       (Description ""
                                                        :> (Summary "Put config for fileSharing"
                                                            :> (CanThrow
                                                                  ('MissingPermission 'Nothing)
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> (CanThrow
                                                                              TeamFeatureError
                                                                            :> (CanThrowMany '[]
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("fileSharing"
                                                                                                :> (ReqBody
                                                                                                      '[JSON]
                                                                                                      (Feature
                                                                                                         FileSharingConfig)
                                                                                                    :> Put
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            FileSharingConfig)))))))))))))
                                                     :<|> Named
                                                            '("ipatch", FileSharingConfig)
                                                            (Description ""
                                                             :> (Summary
                                                                   "Patch config for fileSharing"
                                                                 :> (CanThrow
                                                                       ('MissingPermission 'Nothing)
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("fileSharing"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (LockableFeaturePatch
                                                                                                              FileSharingConfig)
                                                                                                         :> Patch
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 FileSharingConfig)))))))))))))))
                                              :<|> (Named
                                                      '("iget", ClassifiedDomainsConfig)
                                                      (Description ""
                                                       :> (Summary
                                                             "Get config for classifiedDomains"
                                                           :> (CanThrow
                                                                 ('MissingPermission 'Nothing)
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("classifiedDomains"
                                                                                       :> Get
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               ClassifiedDomainsConfig))))))))))
                                                    :<|> ((Named
                                                             '("iget", ConferenceCallingConfig)
                                                             (Description ""
                                                              :> (Summary
                                                                    "Get config for conferenceCalling"
                                                                  :> (CanThrow
                                                                        ('MissingPermission
                                                                           'Nothing)
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("conferenceCalling"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      ConferenceCallingConfig))))))))))
                                                           :<|> (Named
                                                                   '("iput",
                                                                     ConferenceCallingConfig)
                                                                   (Description ""
                                                                    :> (Summary
                                                                          "Put config for conferenceCalling"
                                                                        :> (CanThrow
                                                                              ('MissingPermission
                                                                                 'Nothing)
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> (CanThrow
                                                                                          TeamFeatureError
                                                                                        :> (CanThrowMany
                                                                                              '[]
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("conferenceCalling"
                                                                                                            :> (ReqBody
                                                                                                                  '[JSON]
                                                                                                                  (Feature
                                                                                                                     ConferenceCallingConfig)
                                                                                                                :> Put
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        ConferenceCallingConfig)))))))))))))
                                                                 :<|> Named
                                                                        '("ipatch",
                                                                          ConferenceCallingConfig)
                                                                        (Description ""
                                                                         :> (Summary
                                                                               "Patch config for conferenceCalling"
                                                                             :> (CanThrow
                                                                                   ('MissingPermission
                                                                                      'Nothing)
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("conferenceCalling"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeaturePatch
                                                                                                                          ConferenceCallingConfig)
                                                                                                                     :> Patch
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             ConferenceCallingConfig)))))))))))))))
                                                          :<|> ((Named
                                                                   '("iget",
                                                                     SelfDeletingMessagesConfig)
                                                                   (Description ""
                                                                    :> (Summary
                                                                          "Get config for selfDeletingMessages"
                                                                        :> (CanThrow
                                                                              ('MissingPermission
                                                                                 'Nothing)
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("selfDeletingMessages"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            SelfDeletingMessagesConfig))))))))))
                                                                 :<|> (Named
                                                                         '("iput",
                                                                           SelfDeletingMessagesConfig)
                                                                         (Description ""
                                                                          :> (Summary
                                                                                "Put config for selfDeletingMessages"
                                                                              :> (CanThrow
                                                                                    ('MissingPermission
                                                                                       'Nothing)
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> (CanThrow
                                                                                                TeamFeatureError
                                                                                              :> (CanThrowMany
                                                                                                    '[]
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("selfDeletingMessages"
                                                                                                                  :> (ReqBody
                                                                                                                        '[JSON]
                                                                                                                        (Feature
                                                                                                                           SelfDeletingMessagesConfig)
                                                                                                                      :> Put
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              SelfDeletingMessagesConfig)))))))))))))
                                                                       :<|> Named
                                                                              '("ipatch",
                                                                                SelfDeletingMessagesConfig)
                                                                              (Description ""
                                                                               :> (Summary
                                                                                     "Patch config for selfDeletingMessages"
                                                                                   :> (CanThrow
                                                                                         ('MissingPermission
                                                                                            'Nothing)
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("selfDeletingMessages"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeaturePatch
                                                                                                                                SelfDeletingMessagesConfig)
                                                                                                                           :> Patch
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   SelfDeletingMessagesConfig)))))))))))))))
                                                                :<|> ((Named
                                                                         '("iget", GuestLinksConfig)
                                                                         (Description ""
                                                                          :> (Summary
                                                                                "Get config for conversationGuestLinks"
                                                                              :> (CanThrow
                                                                                    ('MissingPermission
                                                                                       'Nothing)
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("conversationGuestLinks"
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  GuestLinksConfig))))))))))
                                                                       :<|> (Named
                                                                               '("iput",
                                                                                 GuestLinksConfig)
                                                                               (Description ""
                                                                                :> (Summary
                                                                                      "Put config for conversationGuestLinks"
                                                                                    :> (CanThrow
                                                                                          ('MissingPermission
                                                                                             'Nothing)
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> (CanThrow
                                                                                                      TeamFeatureError
                                                                                                    :> (CanThrowMany
                                                                                                          '[]
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("conversationGuestLinks"
                                                                                                                        :> (ReqBody
                                                                                                                              '[JSON]
                                                                                                                              (Feature
                                                                                                                                 GuestLinksConfig)
                                                                                                                            :> Put
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeature
                                                                                                                                    GuestLinksConfig)))))))))))))
                                                                             :<|> Named
                                                                                    '("ipatch",
                                                                                      GuestLinksConfig)
                                                                                    (Description ""
                                                                                     :> (Summary
                                                                                           "Patch config for conversationGuestLinks"
                                                                                         :> (CanThrow
                                                                                               ('MissingPermission
                                                                                                  'Nothing)
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           TeamFeatureError
                                                                                                         :> (CanThrowMany
                                                                                                               '[]
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeaturePatch
                                                                                                                                      GuestLinksConfig)
                                                                                                                                 :> Patch
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         GuestLinksConfig)))))))))))))))
                                                                      :<|> ((Named
                                                                               '("iget",
                                                                                 SndFactorPasswordChallengeConfig)
                                                                               (Description ""
                                                                                :> (Summary
                                                                                      "Get config for sndFactorPasswordChallenge"
                                                                                    :> (CanThrow
                                                                                          ('MissingPermission
                                                                                             'Nothing)
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("sndFactorPasswordChallenge"
                                                                                                                :> Get
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        SndFactorPasswordChallengeConfig))))))))))
                                                                             :<|> (Named
                                                                                     '("iput",
                                                                                       SndFactorPasswordChallengeConfig)
                                                                                     (Description ""
                                                                                      :> (Summary
                                                                                            "Put config for sndFactorPasswordChallenge"
                                                                                          :> (CanThrow
                                                                                                ('MissingPermission
                                                                                                   'Nothing)
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> (CanThrow
                                                                                                            TeamFeatureError
                                                                                                          :> (CanThrowMany
                                                                                                                '[]
                                                                                                              :> ("teams"
                                                                                                                  :> (Capture
                                                                                                                        "tid"
                                                                                                                        TeamId
                                                                                                                      :> ("features"
                                                                                                                          :> ("sndFactorPasswordChallenge"
                                                                                                                              :> (ReqBody
                                                                                                                                    '[JSON]
                                                                                                                                    (Feature
                                                                                                                                       SndFactorPasswordChallengeConfig)
                                                                                                                                  :> Put
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeature
                                                                                                                                          SndFactorPasswordChallengeConfig)))))))))))))
                                                                                   :<|> Named
                                                                                          '("ipatch",
                                                                                            SndFactorPasswordChallengeConfig)
                                                                                          (Description
                                                                                             ""
                                                                                           :> (Summary
                                                                                                 "Patch config for sndFactorPasswordChallenge"
                                                                                               :> (CanThrow
                                                                                                     ('MissingPermission
                                                                                                        'Nothing)
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> (CanThrow
                                                                                                                 TeamFeatureError
                                                                                                               :> (CanThrowMany
                                                                                                                     '[]
                                                                                                                   :> ("teams"
                                                                                                                       :> (Capture
                                                                                                                             "tid"
                                                                                                                             TeamId
                                                                                                                           :> ("features"
                                                                                                                               :> ("sndFactorPasswordChallenge"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeaturePatch
                                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                                       :> Patch
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               SndFactorPasswordChallengeConfig)))))))))))))))
                                                                            :<|> ((Named
                                                                                     '("iget",
                                                                                       MLSConfig)
                                                                                     (Description ""
                                                                                      :> (Summary
                                                                                            "Get config for mls"
                                                                                          :> (CanThrow
                                                                                                ('MissingPermission
                                                                                                   'Nothing)
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("mls"
                                                                                                                      :> Get
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              MLSConfig))))))))))
                                                                                   :<|> (Named
                                                                                           '("iput",
                                                                                             MLSConfig)
                                                                                           (Description
                                                                                              ""
                                                                                            :> (Summary
                                                                                                  "Put config for mls"
                                                                                                :> (CanThrow
                                                                                                      ('MissingPermission
                                                                                                         'Nothing)
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> (CanThrow
                                                                                                                  TeamFeatureError
                                                                                                                :> (CanThrowMany
                                                                                                                      '[]
                                                                                                                    :> ("teams"
                                                                                                                        :> (Capture
                                                                                                                              "tid"
                                                                                                                              TeamId
                                                                                                                            :> ("features"
                                                                                                                                :> ("mls"
                                                                                                                                    :> (ReqBody
                                                                                                                                          '[JSON]
                                                                                                                                          (Feature
                                                                                                                                             MLSConfig)
                                                                                                                                        :> Put
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeature
                                                                                                                                                MLSConfig)))))))))))))
                                                                                         :<|> Named
                                                                                                '("ipatch",
                                                                                                  MLSConfig)
                                                                                                (Description
                                                                                                   ""
                                                                                                 :> (Summary
                                                                                                       "Patch config for mls"
                                                                                                     :> (CanThrow
                                                                                                           ('MissingPermission
                                                                                                              'Nothing)
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       TeamFeatureError
                                                                                                                     :> (CanThrowMany
                                                                                                                           '[]
                                                                                                                         :> ("teams"
                                                                                                                             :> (Capture
                                                                                                                                   "tid"
                                                                                                                                   TeamId
                                                                                                                                 :> ("features"
                                                                                                                                     :> ("mls"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                  MLSConfig)
                                                                                                                                             :> Patch
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     MLSConfig)))))))))))))))
                                                                                  :<|> ((Named
                                                                                           '("iget",
                                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                                           (Description
                                                                                              ""
                                                                                            :> (Summary
                                                                                                  "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                :> (CanThrow
                                                                                                      ('MissingPermission
                                                                                                         'Nothing)
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                            :> Get
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeature
                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                         :<|> (Named
                                                                                                 '("iput",
                                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                                 (Description
                                                                                                    ""
                                                                                                  :> (Summary
                                                                                                        "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                      :> (CanThrow
                                                                                                            ('MissingPermission
                                                                                                               'Nothing)
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> (CanThrow
                                                                                                                        TeamFeatureError
                                                                                                                      :> (CanThrowMany
                                                                                                                            '[]
                                                                                                                          :> ("teams"
                                                                                                                              :> (Capture
                                                                                                                                    "tid"
                                                                                                                                    TeamId
                                                                                                                                  :> ("features"
                                                                                                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                          :> (ReqBody
                                                                                                                                                '[JSON]
                                                                                                                                                (Feature
                                                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                              :> Put
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeature
                                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                               :<|> Named
                                                                                                      '("ipatch",
                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                      (Description
                                                                                                         ""
                                                                                                       :> (Summary
                                                                                                             "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                           :> (CanThrow
                                                                                                                 ('MissingPermission
                                                                                                                    'Nothing)
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             TeamFeatureError
                                                                                                                           :> (CanThrowMany
                                                                                                                                 '[]
                                                                                                                               :> ("teams"
                                                                                                                                   :> (Capture
                                                                                                                                         "tid"
                                                                                                                                         TeamId
                                                                                                                                       :> ("features"
                                                                                                                                           :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                   :> Patch
                                                                                                                                                        '[JSON]
                                                                                                                                                        (LockableFeature
                                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                        :<|> ((Named
                                                                                                 '("iget",
                                                                                                   OutlookCalIntegrationConfig)
                                                                                                 (Description
                                                                                                    ""
                                                                                                  :> (Summary
                                                                                                        "Get config for outlookCalIntegration"
                                                                                                      :> (CanThrow
                                                                                                            ('MissingPermission
                                                                                                               'Nothing)
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("outlookCalIntegration"
                                                                                                                                  :> Get
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeature
                                                                                                                                          OutlookCalIntegrationConfig))))))))))
                                                                                               :<|> (Named
                                                                                                       '("iput",
                                                                                                         OutlookCalIntegrationConfig)
                                                                                                       (Description
                                                                                                          ""
                                                                                                        :> (Summary
                                                                                                              "Put config for outlookCalIntegration"
                                                                                                            :> (CanThrow
                                                                                                                  ('MissingPermission
                                                                                                                     'Nothing)
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          'TeamNotFound
                                                                                                                        :> (CanThrow
                                                                                                                              TeamFeatureError
                                                                                                                            :> (CanThrowMany
                                                                                                                                  '[]
                                                                                                                                :> ("teams"
                                                                                                                                    :> (Capture
                                                                                                                                          "tid"
                                                                                                                                          TeamId
                                                                                                                                        :> ("features"
                                                                                                                                            :> ("outlookCalIntegration"
                                                                                                                                                :> (ReqBody
                                                                                                                                                      '[JSON]
                                                                                                                                                      (Feature
                                                                                                                                                         OutlookCalIntegrationConfig)
                                                                                                                                                    :> Put
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeature
                                                                                                                                                            OutlookCalIntegrationConfig)))))))))))))
                                                                                                     :<|> Named
                                                                                                            '("ipatch",
                                                                                                              OutlookCalIntegrationConfig)
                                                                                                            (Description
                                                                                                               ""
                                                                                                             :> (Summary
                                                                                                                   "Patch config for outlookCalIntegration"
                                                                                                                 :> (CanThrow
                                                                                                                       ('MissingPermission
                                                                                                                          'Nothing)
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   TeamFeatureError
                                                                                                                                 :> (CanThrowMany
                                                                                                                                       '[]
                                                                                                                                     :> ("teams"
                                                                                                                                         :> (Capture
                                                                                                                                               "tid"
                                                                                                                                               TeamId
                                                                                                                                             :> ("features"
                                                                                                                                                 :> ("outlookCalIntegration"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                              OutlookCalIntegrationConfig)
                                                                                                                                                         :> Patch
                                                                                                                                                              '[JSON]
                                                                                                                                                              (LockableFeature
                                                                                                                                                                 OutlookCalIntegrationConfig)))))))))))))))
                                                                                              :<|> ((Named
                                                                                                       '("iget",
                                                                                                         MlsE2EIdConfig)
                                                                                                       (Description
                                                                                                          ""
                                                                                                        :> (Summary
                                                                                                              "Get config for mlsE2EId"
                                                                                                            :> (CanThrow
                                                                                                                  ('MissingPermission
                                                                                                                     'Nothing)
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          'TeamNotFound
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("mlsE2EId"
                                                                                                                                        :> Get
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeature
                                                                                                                                                MlsE2EIdConfig))))))))))
                                                                                                     :<|> (Named
                                                                                                             '("iput",
                                                                                                               MlsE2EIdConfig)
                                                                                                             (Description
                                                                                                                ""
                                                                                                              :> (Summary
                                                                                                                    "Put config for mlsE2EId"
                                                                                                                  :> (CanThrow
                                                                                                                        ('MissingPermission
                                                                                                                           'Nothing)
                                                                                                                      :> (CanThrow
                                                                                                                            'NotATeamMember
                                                                                                                          :> (CanThrow
                                                                                                                                'TeamNotFound
                                                                                                                              :> (CanThrow
                                                                                                                                    TeamFeatureError
                                                                                                                                  :> (CanThrowMany
                                                                                                                                        '[]
                                                                                                                                      :> ("teams"
                                                                                                                                          :> (Capture
                                                                                                                                                "tid"
                                                                                                                                                TeamId
                                                                                                                                              :> ("features"
                                                                                                                                                  :> ("mlsE2EId"
                                                                                                                                                      :> (ReqBody
                                                                                                                                                            '[JSON]
                                                                                                                                                            (Feature
                                                                                                                                                               MlsE2EIdConfig)
                                                                                                                                                          :> Put
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeature
                                                                                                                                                                  MlsE2EIdConfig)))))))))))))
                                                                                                           :<|> Named
                                                                                                                  '("ipatch",
                                                                                                                    MlsE2EIdConfig)
                                                                                                                  (Description
                                                                                                                     ""
                                                                                                                   :> (Summary
                                                                                                                         "Patch config for mlsE2EId"
                                                                                                                       :> (CanThrow
                                                                                                                             ('MissingPermission
                                                                                                                                'Nothing)
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'TeamNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         TeamFeatureError
                                                                                                                                       :> (CanThrowMany
                                                                                                                                             '[]
                                                                                                                                           :> ("teams"
                                                                                                                                               :> (Capture
                                                                                                                                                     "tid"
                                                                                                                                                     TeamId
                                                                                                                                                   :> ("features"
                                                                                                                                                       :> ("mlsE2EId"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                    MlsE2EIdConfig)
                                                                                                                                                               :> Patch
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (LockableFeature
                                                                                                                                                                       MlsE2EIdConfig)))))))))))))))
                                                                                                    :<|> ((Named
                                                                                                             '("iget",
                                                                                                               MlsMigrationConfig)
                                                                                                             (Description
                                                                                                                ""
                                                                                                              :> (Summary
                                                                                                                    "Get config for mlsMigration"
                                                                                                                  :> (CanThrow
                                                                                                                        ('MissingPermission
                                                                                                                           'Nothing)
                                                                                                                      :> (CanThrow
                                                                                                                            'NotATeamMember
                                                                                                                          :> (CanThrow
                                                                                                                                'TeamNotFound
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("mlsMigration"
                                                                                                                                              :> Get
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeature
                                                                                                                                                      MlsMigrationConfig))))))))))
                                                                                                           :<|> (Named
                                                                                                                   '("iput",
                                                                                                                     MlsMigrationConfig)
                                                                                                                   (Description
                                                                                                                      ""
                                                                                                                    :> (Summary
                                                                                                                          "Put config for mlsMigration"
                                                                                                                        :> (CanThrow
                                                                                                                              ('MissingPermission
                                                                                                                                 'Nothing)
                                                                                                                            :> (CanThrow
                                                                                                                                  'NotATeamMember
                                                                                                                                :> (CanThrow
                                                                                                                                      'TeamNotFound
                                                                                                                                    :> (CanThrow
                                                                                                                                          TeamFeatureError
                                                                                                                                        :> (CanThrowMany
                                                                                                                                              '[]
                                                                                                                                            :> ("teams"
                                                                                                                                                :> (Capture
                                                                                                                                                      "tid"
                                                                                                                                                      TeamId
                                                                                                                                                    :> ("features"
                                                                                                                                                        :> ("mlsMigration"
                                                                                                                                                            :> (ReqBody
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (Feature
                                                                                                                                                                     MlsMigrationConfig)
                                                                                                                                                                :> Put
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeature
                                                                                                                                                                        MlsMigrationConfig)))))))))))))
                                                                                                                 :<|> Named
                                                                                                                        '("ipatch",
                                                                                                                          MlsMigrationConfig)
                                                                                                                        (Description
                                                                                                                           ""
                                                                                                                         :> (Summary
                                                                                                                               "Patch config for mlsMigration"
                                                                                                                             :> (CanThrow
                                                                                                                                   ('MissingPermission
                                                                                                                                      'Nothing)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TeamNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               TeamFeatureError
                                                                                                                                             :> (CanThrowMany
                                                                                                                                                   '[]
                                                                                                                                                 :> ("teams"
                                                                                                                                                     :> (Capture
                                                                                                                                                           "tid"
                                                                                                                                                           TeamId
                                                                                                                                                         :> ("features"
                                                                                                                                                             :> ("mlsMigration"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                                          MlsMigrationConfig)
                                                                                                                                                                     :> Patch
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          (LockableFeature
                                                                                                                                                                             MlsMigrationConfig)))))))))))))))
                                                                                                          :<|> ((Named
                                                                                                                   '("iget",
                                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                                   (Description
                                                                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                    :> (Summary
                                                                                                                          "Get config for enforceFileDownloadLocation"
                                                                                                                        :> (CanThrow
                                                                                                                              ('MissingPermission
                                                                                                                                 'Nothing)
                                                                                                                            :> (CanThrow
                                                                                                                                  'NotATeamMember
                                                                                                                                :> (CanThrow
                                                                                                                                      'TeamNotFound
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                                                    :> Get
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeature
                                                                                                                                                            EnforceFileDownloadLocationConfig))))))))))
                                                                                                                 :<|> (Named
                                                                                                                         '("iput",
                                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                                         (Description
                                                                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                          :> (Summary
                                                                                                                                "Put config for enforceFileDownloadLocation"
                                                                                                                              :> (CanThrow
                                                                                                                                    ('MissingPermission
                                                                                                                                       'Nothing)
                                                                                                                                  :> (CanThrow
                                                                                                                                        'NotATeamMember
                                                                                                                                      :> (CanThrow
                                                                                                                                            'TeamNotFound
                                                                                                                                          :> (CanThrow
                                                                                                                                                TeamFeatureError
                                                                                                                                              :> (CanThrowMany
                                                                                                                                                    '[]
                                                                                                                                                  :> ("teams"
                                                                                                                                                      :> (Capture
                                                                                                                                                            "tid"
                                                                                                                                                            TeamId
                                                                                                                                                          :> ("features"
                                                                                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (Feature
                                                                                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                                                                                      :> Put
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeature
                                                                                                                                                                              EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                       :<|> Named
                                                                                                                              '("ipatch",
                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                              (Description
                                                                                                                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                               :> (Summary
                                                                                                                                     "Patch config for enforceFileDownloadLocation"
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('MissingPermission
                                                                                                                                            'Nothing)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'TeamNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     TeamFeatureError
                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                         '[]
                                                                                                                                                       :> ("teams"
                                                                                                                                                           :> (Capture
                                                                                                                                                                 "tid"
                                                                                                                                                                 TeamId
                                                                                                                                                               :> ("features"
                                                                                                                                                                   :> ("enforceFileDownloadLocation"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                                                                           :> Patch
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                   EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                :<|> (Named
                                                                                                                        '("iget",
                                                                                                                          LimitedEventFanoutConfig)
                                                                                                                        (Description
                                                                                                                           ""
                                                                                                                         :> (Summary
                                                                                                                               "Get config for limitedEventFanout"
                                                                                                                             :> (CanThrow
                                                                                                                                   ('MissingPermission
                                                                                                                                      'Nothing)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TeamNotFound
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("limitedEventFanout"
                                                                                                                                                         :> Get
                                                                                                                                                              '[JSON]
                                                                                                                                                              (LockableFeature
                                                                                                                                                                 LimitedEventFanoutConfig))))))))))
                                                                                                                      :<|> (Named
                                                                                                                              '("iput",
                                                                                                                                LimitedEventFanoutConfig)
                                                                                                                              (Description
                                                                                                                                 ""
                                                                                                                               :> (Summary
                                                                                                                                     "Put config for limitedEventFanout"
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('MissingPermission
                                                                                                                                            'Nothing)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'TeamNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     TeamFeatureError
                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                         '[]
                                                                                                                                                       :> ("teams"
                                                                                                                                                           :> (Capture
                                                                                                                                                                 "tid"
                                                                                                                                                                 TeamId
                                                                                                                                                               :> ("features"
                                                                                                                                                                   :> ("limitedEventFanout"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             (Feature
                                                                                                                                                                                LimitedEventFanoutConfig)
                                                                                                                                                                           :> Put
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                   LimitedEventFanoutConfig)))))))))))))
                                                                                                                            :<|> Named
                                                                                                                                   '("ipatch",
                                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Patch config for limitedEventFanout"
                                                                                                                                        :> (CanThrow
                                                                                                                                              ('MissingPermission
                                                                                                                                                 'Nothing)
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("limitedEventFanout"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeaturePatch
                                                                                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                                                                                :> Patch
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
   :<|> (Named
           '("ilock", FileSharingConfig)
           (Summary "(Un-)lock fileSharing"
            :> (Description ""
                :> (CanThrow 'NotATeamMember
                    :> (CanThrow 'TeamNotFound
                        :> ("teams"
                            :> (Capture "tid" TeamId
                                :> ("features"
                                    :> ("fileSharing"
                                        :> (Capture "lockStatus" LockStatus
                                            :> Put '[JSON] LockStatusResponse)))))))))
         :<|> (Named
                 '("ilock", ConferenceCallingConfig)
                 (Summary "(Un-)lock conferenceCalling"
                  :> (Description ""
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("conferenceCalling"
                                              :> (Capture "lockStatus" LockStatus
                                                  :> Put '[JSON] LockStatusResponse)))))))))
               :<|> (Named
                       '("ilock", SelfDeletingMessagesConfig)
                       (Summary "(Un-)lock selfDeletingMessages"
                        :> (Description ""
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("selfDeletingMessages"
                                                    :> (Capture "lockStatus" LockStatus
                                                        :> Put '[JSON] LockStatusResponse)))))))))
                     :<|> (Named
                             '("ilock", GuestLinksConfig)
                             (Summary "(Un-)lock conversationGuestLinks"
                              :> (Description ""
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("conversationGuestLinks"
                                                          :> (Capture "lockStatus" LockStatus
                                                              :> Put
                                                                   '[JSON]
                                                                   LockStatusResponse)))))))))
                           :<|> (Named
                                   '("ilock", SndFactorPasswordChallengeConfig)
                                   (Summary "(Un-)lock sndFactorPasswordChallenge"
                                    :> (Description ""
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("sndFactorPasswordChallenge"
                                                                :> (Capture "lockStatus" LockStatus
                                                                    :> Put
                                                                         '[JSON]
                                                                         LockStatusResponse)))))))))
                                 :<|> (Named
                                         '("ilock", MLSConfig)
                                         (Summary "(Un-)lock mls"
                                          :> (Description ""
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("mls"
                                                                      :> (Capture
                                                                            "lockStatus" LockStatus
                                                                          :> Put
                                                                               '[JSON]
                                                                               LockStatusResponse)))))))))
                                       :<|> (Named
                                               '("ilock", OutlookCalIntegrationConfig)
                                               (Summary "(Un-)lock outlookCalIntegration"
                                                :> (Description ""
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("outlookCalIntegration"
                                                                            :> (Capture
                                                                                  "lockStatus"
                                                                                  LockStatus
                                                                                :> Put
                                                                                     '[JSON]
                                                                                     LockStatusResponse)))))))))
                                             :<|> (Named
                                                     '("ilock", MlsE2EIdConfig)
                                                     (Summary "(Un-)lock mlsE2EId"
                                                      :> (Description ""
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("mlsE2EId"
                                                                                  :> (Capture
                                                                                        "lockStatus"
                                                                                        LockStatus
                                                                                      :> Put
                                                                                           '[JSON]
                                                                                           LockStatusResponse)))))))))
                                                   :<|> (Named
                                                           '("ilock", MlsMigrationConfig)
                                                           (Summary "(Un-)lock mlsMigration"
                                                            :> (Description ""
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("mlsMigration"
                                                                                        :> (Capture
                                                                                              "lockStatus"
                                                                                              LockStatus
                                                                                            :> Put
                                                                                                 '[JSON]
                                                                                                 LockStatusResponse)))))))))
                                                         :<|> (Named
                                                                 '("ilock",
                                                                   EnforceFileDownloadLocationConfig)
                                                                 (Summary
                                                                    "(Un-)lock enforceFileDownloadLocation"
                                                                  :> (Description
                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("enforceFileDownloadLocation"
                                                                                              :> (Capture
                                                                                                    "lockStatus"
                                                                                                    LockStatus
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       LockStatusResponse)))))))))
                                                               :<|> (Named
                                                                       '("igetmulti",
                                                                         SearchVisibilityInboundConfig)
                                                                       (Summary
                                                                          "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                        :> ("features-multi-teams"
                                                                            :> ("searchVisibilityInbound"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      TeamFeatureNoConfigMultiRequest
                                                                                    :> Post
                                                                                         '[JSON]
                                                                                         (TeamFeatureNoConfigMultiResponse
                                                                                            SearchVisibilityInboundConfig)))))
                                                                     :<|> Named
                                                                            "feature-configs-internal"
                                                                            (Summary
                                                                               "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                             :> ("feature-configs"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (QueryParam'
                                                                                                   '[Optional,
                                                                                                     Strict,
                                                                                                     Description
                                                                                                       "Optional user id"]
                                                                                                   "user_id"
                                                                                                   UserId
                                                                                                 :> Get
                                                                                                      '[JSON]
                                                                                                      AllTeamFeatures))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     (IFederationAPI :<|> (IConversationAPI :<|> IEJPDAPI))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
           '("iget", LegalholdConfig)
           (Description ""
            :> (Summary "Get config for legalhold"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> ("teams"
                                :> (Capture "tid" TeamId
                                    :> ("features"
                                        :> ("legalhold"
                                            :> Get
                                                 '[JSON] (LockableFeature LegalholdConfig))))))))))
         :<|> (Named
                 '("iput", LegalholdConfig)
                 (Description ""
                  :> (Summary "Put config for legalhold"
                      :> (CanThrow ('MissingPermission 'Nothing)
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> (CanThrow TeamFeatureError
                                      :> (CanThrowMany
                                            '[ 'ActionDenied 'RemoveConversationMember,
                                               'CannotEnableLegalHoldServiceLargeTeam,
                                               'LegalHoldNotEnabled, 'LegalHoldDisableUnimplemented,
                                               'LegalHoldServiceNotRegistered,
                                               'UserLegalHoldIllegalOperation,
                                               'LegalHoldCouldNotBlockConnections]
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("legalhold"
                                                          :> (ReqBody
                                                                '[JSON] (Feature LegalholdConfig)
                                                              :> Put
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      LegalholdConfig)))))))))))))
               :<|> Named
                      '("ipatch", LegalholdConfig)
                      (Description ""
                       :> (Summary "Patch config for legalhold"
                           :> (CanThrow ('MissingPermission 'Nothing)
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany
                                                 '[ 'ActionDenied 'RemoveConversationMember,
                                                    'CannotEnableLegalHoldServiceLargeTeam,
                                                    'LegalHoldNotEnabled,
                                                    'LegalHoldDisableUnimplemented,
                                                    'LegalHoldServiceNotRegistered,
                                                    'UserLegalHoldIllegalOperation,
                                                    'LegalHoldCouldNotBlockConnections]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("legalhold"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     (LockableFeaturePatch
                                                                        LegalholdConfig)
                                                                   :> Patch
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           LegalholdConfig)))))))))))))))
        :<|> ((Named
                 '("iget", SSOConfig)
                 (Description ""
                  :> (Summary "Get config for sso"
                      :> (CanThrow ('MissingPermission 'Nothing)
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("sso"
                                                  :> Get
                                                       '[JSON] (LockableFeature SSOConfig))))))))))
               :<|> (Named
                       '("iput", SSOConfig)
                       (Description ""
                        :> (Summary "Put config for sso"
                            :> (CanThrow ('MissingPermission 'Nothing)
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> (CanThrow TeamFeatureError
                                            :> (CanThrowMany '[]
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("sso"
                                                                :> (ReqBody
                                                                      '[JSON] (Feature SSOConfig)
                                                                    :> Put
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            SSOConfig)))))))))))))
                     :<|> Named
                            '("ipatch", SSOConfig)
                            (Description ""
                             :> (Summary "Patch config for sso"
                                 :> (CanThrow ('MissingPermission 'Nothing)
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow TeamFeatureError
                                                 :> (CanThrowMany '[]
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("sso"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           (LockableFeaturePatch
                                                                              SSOConfig)
                                                                         :> Patch
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 SSOConfig)))))))))))))))
              :<|> ((Named
                       '("iget", SearchVisibilityAvailableConfig)
                       (Description ""
                        :> (Summary "Get config for searchVisibility"
                            :> (CanThrow ('MissingPermission 'Nothing)
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("searchVisibility"
                                                        :> Get
                                                             '[JSON]
                                                             (LockableFeature
                                                                SearchVisibilityAvailableConfig))))))))))
                     :<|> (Named
                             '("iput", SearchVisibilityAvailableConfig)
                             (Description ""
                              :> (Summary "Put config for searchVisibility"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> (CanThrow TeamFeatureError
                                                  :> (CanThrowMany '[]
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("searchVisibility"
                                                                      :> (ReqBody
                                                                            '[JSON]
                                                                            (Feature
                                                                               SearchVisibilityAvailableConfig)
                                                                          :> Put
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  SearchVisibilityAvailableConfig)))))))))))))
                           :<|> Named
                                  '("ipatch", SearchVisibilityAvailableConfig)
                                  (Description ""
                                   :> (Summary "Patch config for searchVisibility"
                                       :> (CanThrow ('MissingPermission 'Nothing)
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany '[]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("searchVisibility"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (LockableFeaturePatch
                                                                                    SearchVisibilityAvailableConfig)
                                                                               :> Patch
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       SearchVisibilityAvailableConfig)))))))))))))))
                    :<|> ((Named
                             '("iget", SearchVisibilityInboundConfig)
                             (Description ""
                              :> (Summary "Get config for searchVisibilityInbound"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("searchVisibilityInbound"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      SearchVisibilityInboundConfig))))))))))
                           :<|> (Named
                                   '("iput", SearchVisibilityInboundConfig)
                                   (Description ""
                                    :> (Summary "Put config for searchVisibilityInbound"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> (CanThrow TeamFeatureError
                                                        :> (CanThrowMany '[]
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("searchVisibilityInbound"
                                                                            :> (ReqBody
                                                                                  '[JSON]
                                                                                  (Feature
                                                                                     SearchVisibilityInboundConfig)
                                                                                :> Put
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SearchVisibilityInboundConfig)))))))))))))
                                 :<|> Named
                                        '("ipatch", SearchVisibilityInboundConfig)
                                        (Description ""
                                         :> (Summary "Patch config for searchVisibilityInbound"
                                             :> (CanThrow ('MissingPermission 'Nothing)
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("searchVisibilityInbound"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (LockableFeaturePatch
                                                                                          SearchVisibilityInboundConfig)
                                                                                     :> Patch
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             SearchVisibilityInboundConfig)))))))))))))))
                          :<|> ((Named
                                   '("iget", ValidateSAMLEmailsConfig)
                                   (Description ""
                                    :> (Summary "Get config for validateSAMLemails"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("validateSAMLemails"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            ValidateSAMLEmailsConfig))))))))))
                                 :<|> (Named
                                         '("iput", ValidateSAMLEmailsConfig)
                                         (Description ""
                                          :> (Summary "Put config for validateSAMLemails"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow TeamFeatureError
                                                              :> (CanThrowMany '[]
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("validateSAMLemails"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        (Feature
                                                                                           ValidateSAMLEmailsConfig)
                                                                                      :> Put
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              ValidateSAMLEmailsConfig)))))))))))))
                                       :<|> Named
                                              '("ipatch", ValidateSAMLEmailsConfig)
                                              (Description ""
                                               :> (Summary "Patch config for validateSAMLemails"
                                                   :> (CanThrow ('MissingPermission 'Nothing)
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("validateSAMLemails"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (LockableFeaturePatch
                                                                                                ValidateSAMLEmailsConfig)
                                                                                           :> Patch
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   ValidateSAMLEmailsConfig)))))))))))))))
                                :<|> ((Named
                                         '("iget", DigitalSignaturesConfig)
                                         (Description ""
                                          :> (Summary "Get config for digitalSignatures"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("digitalSignatures"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  DigitalSignaturesConfig))))))))))
                                       :<|> (Named
                                               '("iput", DigitalSignaturesConfig)
                                               (Description ""
                                                :> (Summary "Put config for digitalSignatures"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> (CanThrowMany '[]
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("digitalSignatures"
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              (Feature
                                                                                                 DigitalSignaturesConfig)
                                                                                            :> Put
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    DigitalSignaturesConfig)))))))))))))
                                             :<|> Named
                                                    '("ipatch", DigitalSignaturesConfig)
                                                    (Description ""
                                                     :> (Summary
                                                           "Patch config for digitalSignatures"
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("digitalSignatures"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (LockableFeaturePatch
                                                                                                      DigitalSignaturesConfig)
                                                                                                 :> Patch
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         DigitalSignaturesConfig)))))))))))))))
                                      :<|> ((Named
                                               '("iget", AppLockConfig)
                                               (Description ""
                                                :> (Summary "Get config for appLock"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("appLock"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        AppLockConfig))))))))))
                                             :<|> (Named
                                                     '("iput", AppLockConfig)
                                                     (Description ""
                                                      :> (Summary "Put config for appLock"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany '[]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("appLock"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (Feature
                                                                                                       AppLockConfig)
                                                                                                  :> Put
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          AppLockConfig)))))))))))))
                                                   :<|> Named
                                                          '("ipatch", AppLockConfig)
                                                          (Description ""
                                                           :> (Summary "Patch config for appLock"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("appLock"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (LockableFeaturePatch
                                                                                                            AppLockConfig)
                                                                                                       :> Patch
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               AppLockConfig)))))))))))))))
                                            :<|> ((Named
                                                     '("iget", FileSharingConfig)
                                                     (Description ""
                                                      :> (Summary "Get config for fileSharing"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("fileSharing"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              FileSharingConfig))))))))))
                                                   :<|> (Named
                                                           '("iput", FileSharingConfig)
                                                           (Description ""
                                                            :> (Summary "Put config for fileSharing"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("fileSharing"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (Feature
                                                                                                             FileSharingConfig)
                                                                                                        :> Put
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                FileSharingConfig)))))))))))))
                                                         :<|> Named
                                                                '("ipatch", FileSharingConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Patch config for fileSharing"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("fileSharing"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (LockableFeaturePatch
                                                                                                                  FileSharingConfig)
                                                                                                             :> Patch
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     FileSharingConfig)))))))))))))))
                                                  :<|> (Named
                                                          '("iget", ClassifiedDomainsConfig)
                                                          (Description ""
                                                           :> (Summary
                                                                 "Get config for classifiedDomains"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("classifiedDomains"
                                                                                           :> Get
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   ClassifiedDomainsConfig))))))))))
                                                        :<|> ((Named
                                                                 '("iget", ConferenceCallingConfig)
                                                                 (Description ""
                                                                  :> (Summary
                                                                        "Get config for conferenceCalling"
                                                                      :> (CanThrow
                                                                            ('MissingPermission
                                                                               'Nothing)
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("conferenceCalling"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          ConferenceCallingConfig))))))))))
                                                               :<|> (Named
                                                                       '("iput",
                                                                         ConferenceCallingConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Put config for conferenceCalling"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("conferenceCalling"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (Feature
                                                                                                                         ConferenceCallingConfig)
                                                                                                                    :> Put
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            ConferenceCallingConfig)))))))))))))
                                                                     :<|> Named
                                                                            '("ipatch",
                                                                              ConferenceCallingConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Patch config for conferenceCalling"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("conferenceCalling"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeaturePatch
                                                                                                                              ConferenceCallingConfig)
                                                                                                                         :> Patch
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 ConferenceCallingConfig)))))))))))))))
                                                              :<|> ((Named
                                                                       '("iget",
                                                                         SelfDeletingMessagesConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Get config for selfDeletingMessages"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("selfDeletingMessages"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SelfDeletingMessagesConfig))))))))))
                                                                     :<|> (Named
                                                                             '("iput",
                                                                               SelfDeletingMessagesConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Put config for selfDeletingMessages"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("selfDeletingMessages"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (Feature
                                                                                                                               SelfDeletingMessagesConfig)
                                                                                                                          :> Put
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  SelfDeletingMessagesConfig)))))))))))))
                                                                           :<|> Named
                                                                                  '("ipatch",
                                                                                    SelfDeletingMessagesConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Patch config for selfDeletingMessages"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("selfDeletingMessages"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeaturePatch
                                                                                                                                    SelfDeletingMessagesConfig)
                                                                                                                               :> Patch
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       SelfDeletingMessagesConfig)))))))))))))))
                                                                    :<|> ((Named
                                                                             '("iget",
                                                                               GuestLinksConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Get config for conversationGuestLinks"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("conversationGuestLinks"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      GuestLinksConfig))))))))))
                                                                           :<|> (Named
                                                                                   '("iput",
                                                                                     GuestLinksConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Put config for conversationGuestLinks"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("conversationGuestLinks"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (Feature
                                                                                                                                     GuestLinksConfig)
                                                                                                                                :> Put
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        GuestLinksConfig)))))))))))))
                                                                                 :<|> Named
                                                                                        '("ipatch",
                                                                                          GuestLinksConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Patch config for conversationGuestLinks"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeaturePatch
                                                                                                                                          GuestLinksConfig)
                                                                                                                                     :> Patch
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             GuestLinksConfig)))))))))))))))
                                                                          :<|> ((Named
                                                                                   '("iget",
                                                                                     SndFactorPasswordChallengeConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Get config for sndFactorPasswordChallenge"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("sndFactorPasswordChallenge"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            SndFactorPasswordChallengeConfig))))))))))
                                                                                 :<|> (Named
                                                                                         '("iput",
                                                                                           SndFactorPasswordChallengeConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Put config for sndFactorPasswordChallenge"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("sndFactorPasswordChallenge"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (Feature
                                                                                                                                           SndFactorPasswordChallengeConfig)
                                                                                                                                      :> Put
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              SndFactorPasswordChallengeConfig)))))))))))))
                                                                                       :<|> Named
                                                                                              '("ipatch",
                                                                                                SndFactorPasswordChallengeConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Patch config for sndFactorPasswordChallenge"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                                                           :> Patch
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                :<|> ((Named
                                                                                         '("iget",
                                                                                           MLSConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Get config for mls"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mls"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  MLSConfig))))))))))
                                                                                       :<|> (Named
                                                                                               '("iput",
                                                                                                 MLSConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Put config for mls"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("mls"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (Feature
                                                                                                                                                 MLSConfig)
                                                                                                                                            :> Put
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    MLSConfig)))))))))))))
                                                                                             :<|> Named
                                                                                                    '("ipatch",
                                                                                                      MLSConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Patch config for mls"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("mls"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                      MLSConfig)
                                                                                                                                                 :> Patch
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         MLSConfig)))))))))))))))
                                                                                      :<|> ((Named
                                                                                               '("iget",
                                                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                             :<|> (Named
                                                                                                     '("iput",
                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Feature
                                                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                  :> Put
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                   :<|> Named
                                                                                                          '("ipatch",
                                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                       :> Patch
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                            :<|> ((Named
                                                                                                     '("iget",
                                                                                                       OutlookCalIntegrationConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Get config for outlookCalIntegration"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("outlookCalIntegration"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              OutlookCalIntegrationConfig))))))))))
                                                                                                   :<|> (Named
                                                                                                           '("iput",
                                                                                                             OutlookCalIntegrationConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Put config for outlookCalIntegration"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("outlookCalIntegration"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Feature
                                                                                                                                                             OutlookCalIntegrationConfig)
                                                                                                                                                        :> Put
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                OutlookCalIntegrationConfig)))))))))))))
                                                                                                         :<|> Named
                                                                                                                '("ipatch",
                                                                                                                  OutlookCalIntegrationConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Patch config for outlookCalIntegration"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("outlookCalIntegration"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                  OutlookCalIntegrationConfig)
                                                                                                                                                             :> Patch
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     OutlookCalIntegrationConfig)))))))))))))))
                                                                                                  :<|> ((Named
                                                                                                           '("iget",
                                                                                                             MlsE2EIdConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Get config for mlsE2EId"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("mlsE2EId"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    MlsE2EIdConfig))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iput",
                                                                                                                   MlsE2EIdConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Put config for mlsE2EId"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("mlsE2EId"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Feature
                                                                                                                                                                   MlsE2EIdConfig)
                                                                                                                                                              :> Put
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      MlsE2EIdConfig)))))))))))))
                                                                                                               :<|> Named
                                                                                                                      '("ipatch",
                                                                                                                        MlsE2EIdConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Patch config for mlsE2EId"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("mlsE2EId"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                        MlsE2EIdConfig)
                                                                                                                                                                   :> Patch
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           MlsE2EIdConfig)))))))))))))))
                                                                                                        :<|> ((Named
                                                                                                                 '("iget",
                                                                                                                   MlsMigrationConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for mlsMigration"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("mlsMigration"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          MlsMigrationConfig))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iput",
                                                                                                                         MlsMigrationConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Put config for mlsMigration"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("mlsMigration"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Feature
                                                                                                                                                                         MlsMigrationConfig)
                                                                                                                                                                    :> Put
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MlsMigrationConfig)))))))))))))
                                                                                                                     :<|> Named
                                                                                                                            '("ipatch",
                                                                                                                              MlsMigrationConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Patch config for mlsMigration"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("mlsMigration"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeaturePatch
                                                                                                                                                                              MlsMigrationConfig)
                                                                                                                                                                         :> Patch
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 MlsMigrationConfig)))))))))))))))
                                                                                                              :<|> ((Named
                                                                                                                       '("iget",
                                                                                                                         EnforceFileDownloadLocationConfig)
                                                                                                                       (Description
                                                                                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                        :> (Summary
                                                                                                                              "Get config for enforceFileDownloadLocation"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                EnforceFileDownloadLocationConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                             (Description
                                                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for enforceFileDownloadLocation"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                                  (Description
                                                                                                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for enforceFileDownloadLocation"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("enforceFileDownloadLocation"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                    :<|> (Named
                                                                                                                            '("iget",
                                                                                                                              LimitedEventFanoutConfig)
                                                                                                                            (Description
                                                                                                                               ""
                                                                                                                             :> (Summary
                                                                                                                                   "Get config for limitedEventFanout"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("teams"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "tid"
                                                                                                                                                       TeamId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("limitedEventFanout"
                                                                                                                                                             :> Get
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     LimitedEventFanoutConfig))))))))))
                                                                                                                          :<|> (Named
                                                                                                                                  '("iput",
                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Put config for limitedEventFanout"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("limitedEventFanout"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (Feature
                                                                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                                                               :> Put
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       LimitedEventFanoutConfig)))))))))))))
                                                                                                                                :<|> Named
                                                                                                                                       '("ipatch",
                                                                                                                                         LimitedEventFanoutConfig)
                                                                                                                                       (Description
                                                                                                                                          ""
                                                                                                                                        :> (Summary
                                                                                                                                              "Patch config for limitedEventFanout"
                                                                                                                                            :> (CanThrow
                                                                                                                                                  ('MissingPermission
                                                                                                                                                     'Nothing)
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'NotATeamMember
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          'TeamNotFound
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              TeamFeatureError
                                                                                                                                                            :> (CanThrowMany
                                                                                                                                                                  '[]
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("limitedEventFanout"
                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      (LockableFeaturePatch
                                                                                                                                                                                         LimitedEventFanoutConfig)
                                                                                                                                                                                    :> Patch
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                            LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
       :<|> (Named
               '("ilock", FileSharingConfig)
               (Summary "(Un-)lock fileSharing"
                :> (Description ""
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> ("teams"
                                :> (Capture "tid" TeamId
                                    :> ("features"
                                        :> ("fileSharing"
                                            :> (Capture "lockStatus" LockStatus
                                                :> Put '[JSON] LockStatusResponse)))))))))
             :<|> (Named
                     '("ilock", ConferenceCallingConfig)
                     (Summary "(Un-)lock conferenceCalling"
                      :> (Description ""
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("conferenceCalling"
                                                  :> (Capture "lockStatus" LockStatus
                                                      :> Put '[JSON] LockStatusResponse)))))))))
                   :<|> (Named
                           '("ilock", SelfDeletingMessagesConfig)
                           (Summary "(Un-)lock selfDeletingMessages"
                            :> (Description ""
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("selfDeletingMessages"
                                                        :> (Capture "lockStatus" LockStatus
                                                            :> Put
                                                                 '[JSON] LockStatusResponse)))))))))
                         :<|> (Named
                                 '("ilock", GuestLinksConfig)
                                 (Summary "(Un-)lock conversationGuestLinks"
                                  :> (Description ""
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("conversationGuestLinks"
                                                              :> (Capture "lockStatus" LockStatus
                                                                  :> Put
                                                                       '[JSON]
                                                                       LockStatusResponse)))))))))
                               :<|> (Named
                                       '("ilock", SndFactorPasswordChallengeConfig)
                                       (Summary "(Un-)lock sndFactorPasswordChallenge"
                                        :> (Description ""
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("sndFactorPasswordChallenge"
                                                                    :> (Capture
                                                                          "lockStatus" LockStatus
                                                                        :> Put
                                                                             '[JSON]
                                                                             LockStatusResponse)))))))))
                                     :<|> (Named
                                             '("ilock", MLSConfig)
                                             (Summary "(Un-)lock mls"
                                              :> (Description ""
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("mls"
                                                                          :> (Capture
                                                                                "lockStatus"
                                                                                LockStatus
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   LockStatusResponse)))))))))
                                           :<|> (Named
                                                   '("ilock", OutlookCalIntegrationConfig)
                                                   (Summary "(Un-)lock outlookCalIntegration"
                                                    :> (Description ""
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("outlookCalIntegration"
                                                                                :> (Capture
                                                                                      "lockStatus"
                                                                                      LockStatus
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         LockStatusResponse)))))))))
                                                 :<|> (Named
                                                         '("ilock", MlsE2EIdConfig)
                                                         (Summary "(Un-)lock mlsE2EId"
                                                          :> (Description ""
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("mlsE2EId"
                                                                                      :> (Capture
                                                                                            "lockStatus"
                                                                                            LockStatus
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               LockStatusResponse)))))))))
                                                       :<|> (Named
                                                               '("ilock", MlsMigrationConfig)
                                                               (Summary "(Un-)lock mlsMigration"
                                                                :> (Description ""
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mlsMigration"
                                                                                            :> (Capture
                                                                                                  "lockStatus"
                                                                                                  LockStatus
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     LockStatusResponse)))))))))
                                                             :<|> (Named
                                                                     '("ilock",
                                                                       EnforceFileDownloadLocationConfig)
                                                                     (Summary
                                                                        "(Un-)lock enforceFileDownloadLocation"
                                                                      :> (Description
                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                  :> (Capture
                                                                                                        "lockStatus"
                                                                                                        LockStatus
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           LockStatusResponse)))))))))
                                                                   :<|> (Named
                                                                           '("igetmulti",
                                                                             SearchVisibilityInboundConfig)
                                                                           (Summary
                                                                              "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                            :> ("features-multi-teams"
                                                                                :> ("searchVisibilityInbound"
                                                                                    :> (ReqBody
                                                                                          '[JSON]
                                                                                          TeamFeatureNoConfigMultiRequest
                                                                                        :> Post
                                                                                             '[JSON]
                                                                                             (TeamFeatureNoConfigMultiResponse
                                                                                                SearchVisibilityInboundConfig)))))
                                                                         :<|> Named
                                                                                "feature-configs-internal"
                                                                                (Summary
                                                                                   "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                 :> ("feature-configs"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (QueryParam'
                                                                                                       '[Optional,
                                                                                                         Strict,
                                                                                                         Description
                                                                                                           "Optional user id"]
                                                                                                       "user_id"
                                                                                                       UserId
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          AllTeamFeatures))))))))))))))))))
      :<|> (IFederationAPI :<|> (IConversationAPI :<|> IEJPDAPI)))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  IFederationAPI
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 IFederationAPI GalleyEffects
federationAPI
      API
  IFederationAPI
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     (IConversationAPI :<|> IEJPDAPI)
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
     (IFederationAPI :<|> (IConversationAPI :<|> IEJPDAPI))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  IConversationAPI
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 IConversationAPI GalleyEffects
conversationAPI
      API
  IConversationAPI
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     IEJPDAPI
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
     (IConversationAPI :<|> IEJPDAPI)
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  IEJPDAPI
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 IEJPDAPI GalleyEffects
iEJPDAPI

iEJPDAPI :: API IEJPDAPI GalleyEffects
iEJPDAPI :: API IEJPDAPI GalleyEffects
iEJPDAPI = 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-by-user" (((() :: Constraint) =>
 UserId
 -> Sem
      '[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]
      [EJPDConvInfo])
-> UserId
-> Sem
     '[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]
     [EJPDConvInfo]
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((UserId
 -> Sem
      '[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]
      [EJPDConvInfo])
-> UserId
-> Sem
     '[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]
     [EJPDConvInfo]
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations UserId
-> Sem
     '[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]
     [EJPDConvInfo]
forall (r :: EffectRow) p.
(p ~ CassandraPaging, Member ConversationStore r,
 Member (Error InternalError) r, Member (Input (Local ())) r,
 Member (Input Env) r, Member (ListItems p ConvId) r,
 Member (ListItems p (Remote ConvId)) r,
 Member (Logger (Msg -> Msg)) r) =>
UserId -> Sem r [EJPDConvInfo]
ejpdGetConvInfo))

-- | An unpaginated, internal http interface to `Query.conversationIdsPageFrom`.  Used for
-- EJPD reports.  Called locally with very little data for each conv, so we don't expect
-- pagination to ever be needed.
ejpdGetConvInfo ::
  forall r p.
  ( p ~ CassandraPaging,
    Member ConversationStore r,
    Member (Error InternalError) r,
    Member (Input (Local ())) r,
    Member (Input Env) r,
    Member (ListItems p ConvId) r,
    Member (ListItems p (Remote ConvId)) r,
    Member P.TinyLog r
  ) =>
  UserId ->
  Sem r [EJPDConvInfo]
ejpdGetConvInfo :: forall (r :: EffectRow) p.
(p ~ CassandraPaging, Member ConversationStore r,
 Member (Error InternalError) r, Member (Input (Local ())) r,
 Member (Input Env) r, Member (ListItems p ConvId) r,
 Member (ListItems p (Remote ConvId)) r,
 Member (Logger (Msg -> Msg)) r) =>
UserId -> Sem r [EJPDConvInfo]
ejpdGetConvInfo UserId
uid = do
  QualifiedWithTag 'QLocal UserId
luid <- UserId -> Sem r (QualifiedWithTag 'QLocal UserId)
forall (r :: EffectRow) a.
Member (Input (Local ())) r =>
a -> Sem r (Local a)
qualifyLocal UserId
uid
  ConvIdsPage
firstPage <- QualifiedWithTag 'QLocal UserId
-> GetPaginatedConversationIds -> Sem r 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
Query.conversationIdsPageFrom QualifiedWithTag 'QLocal UserId
luid GetPaginatedConversationIds
initialPageRequest
  QualifiedWithTag 'QLocal UserId
-> ConvIdsPage -> Sem r [EJPDConvInfo]
getPages QualifiedWithTag 'QLocal UserId
luid ConvIdsPage
firstPage
  where
    initialPageRequest :: GetPaginatedConversationIds
initialPageRequest = MultiTablePagingState ConversationPagingName LocalOrRemoteTable
-> GetPaginatedConversationIds
forall {name :: Symbol} {tables} {def :: Nat}.
MultiTablePagingState name tables
-> GetMultiTablePageRequest name tables 1000 def
mkPageRequest (LocalOrRemoteTable
-> Maybe ByteString
-> MultiTablePagingState ConversationPagingName LocalOrRemoteTable
forall (name :: Symbol) tables.
tables -> Maybe ByteString -> MultiTablePagingState name tables
MTP.MultiTablePagingState LocalOrRemoteTable
MTP.PagingLocals Maybe ByteString
forall a. Maybe a
Nothing)
    mkPageRequest :: MultiTablePagingState name tables
-> GetMultiTablePageRequest name tables 1000 def
mkPageRequest = Range 1 1000 Int32
-> Maybe (MultiTablePagingState name tables)
-> GetMultiTablePageRequest name tables 1000 def
forall (name :: Symbol) tables (max :: Nat) (def :: Nat).
Range 1 max Int32
-> Maybe (MultiTablePagingState name tables)
-> GetMultiTablePageRequest name tables max def
MTP.GetMultiTablePageRequest (Proxy 1000 -> Range 1 1000 Int32
forall (n :: Nat) (x :: Nat) (m :: Nat) a.
(n <= x, x <= m, KnownNat x, Num a) =>
Proxy x -> Range n m a
toRange (forall (t :: Nat). Proxy t
forall {k} (t :: k). Proxy t
Proxy @1000)) (Maybe (MultiTablePagingState name tables)
 -> GetMultiTablePageRequest name tables 1000 def)
-> (MultiTablePagingState name tables
    -> Maybe (MultiTablePagingState name tables))
-> MultiTablePagingState name tables
-> GetMultiTablePageRequest name tables 1000 def
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MultiTablePagingState name tables
-> Maybe (MultiTablePagingState name tables)
forall a. a -> Maybe a
Just

    getPages :: Local UserId -> ConvIdsPage -> Sem r [EJPDConvInfo]
    getPages :: QualifiedWithTag 'QLocal UserId
-> ConvIdsPage -> Sem r [EJPDConvInfo]
getPages QualifiedWithTag 'QLocal UserId
luid ConvIdsPage
page = do
      let convids :: [Qualified ConvId]
convids = ConvIdsPage -> [Qualified ConvId]
forall (name :: Symbol) (resultsKey :: Symbol) tables a.
MultiTablePage name resultsKey tables a -> [a]
MTP.mtpResults ConvIdsPage
page
          mk :: Data.Conversation -> Maybe EJPDConvInfo
          mk :: Conversation -> Maybe EJPDConvInfo
mk Conversation
conv = do
            let convType :: ConvType
convType = Conversation
conv.convMetadata.cnvmType
                ejpdConvInfo :: EJPDConvInfo
ejpdConvInfo = Text -> Qualified ConvId -> EJPDConvInfo
EJPDConvInfo (Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"n/a" Conversation
conv.convMetadata.cnvmName) (QualifiedWithTag 'QLocal ConvId -> Qualified ConvId
forall (t :: QTag) a. QualifiedWithTag t a -> Qualified a
tUntagged (QualifiedWithTag 'QLocal ConvId -> Qualified ConvId)
-> QualifiedWithTag 'QLocal ConvId -> Qualified ConvId
forall a b. (a -> b) -> a -> b
$ QualifiedWithTag 'QLocal UserId
-> ConvId -> QualifiedWithTag 'QLocal ConvId
forall (t :: QTag) x a.
QualifiedWithTag t x -> a -> QualifiedWithTag t a
qualifyAs QualifiedWithTag 'QLocal UserId
luid Conversation
conv.convId)
            -- we don't want self conversations as they don't tell us anything about connections
            -- we don't want connect conversations, because the peer has not responded yet
            case ConvType
convType of
              ConvType
RegularConv -> EJPDConvInfo -> Maybe EJPDConvInfo
forall a. a -> Maybe a
Just EJPDConvInfo
ejpdConvInfo
              -- FUTUREWORK(mangoiv): with GHC 9.12 we can refactor this to or-patterns
              ConvType
One2OneConv -> Maybe EJPDConvInfo
forall a. Maybe a
Nothing
              ConvType
SelfConv -> Maybe EJPDConvInfo
forall a. Maybe a
Nothing
              ConvType
ConnectConv -> Maybe EJPDConvInfo
forall a. Maybe a
Nothing
      [EJPDConvInfo]
renderedPage <- (Conversation -> Maybe EJPDConvInfo)
-> [Conversation] -> [EJPDConvInfo]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Conversation -> Maybe EJPDConvInfo
mk ([Conversation] -> [EJPDConvInfo])
-> Sem r [Conversation] -> Sem r [EJPDConvInfo]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ConvId] -> Sem r [Conversation]
forall (r :: EffectRow).
Member ConversationStore r =>
[ConvId] -> Sem r [Conversation]
getConversations (([ConvId], [Remote ConvId]) -> [ConvId]
forall a b. (a, b) -> a
fst (([ConvId], [Remote ConvId]) -> [ConvId])
-> ([ConvId], [Remote ConvId]) -> [ConvId]
forall a b. (a -> b) -> a -> b
$ QualifiedWithTag 'QLocal UserId
-> [Qualified ConvId] -> ([ConvId], [Remote ConvId])
forall (f :: * -> *) x a.
Foldable f =>
Local x -> f (Qualified a) -> ([a], [Remote a])
partitionQualified QualifiedWithTag 'QLocal UserId
luid [Qualified ConvId]
convids)
      if ConvIdsPage -> Bool
forall (name :: Symbol) (resultsKey :: Symbol) tables a.
MultiTablePage name resultsKey tables a -> Bool
MTP.mtpHasMore ConvIdsPage
page
        then do
          ConvIdsPage
newPage <- QualifiedWithTag 'QLocal UserId
-> GetPaginatedConversationIds -> Sem r 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
Query.conversationIdsPageFrom QualifiedWithTag 'QLocal UserId
luid (MultiTablePagingState ConversationPagingName LocalOrRemoteTable
-> GetPaginatedConversationIds
forall {name :: Symbol} {tables} {def :: Nat}.
MultiTablePagingState name tables
-> GetMultiTablePageRequest name tables 1000 def
mkPageRequest (MultiTablePagingState ConversationPagingName LocalOrRemoteTable
 -> GetPaginatedConversationIds)
-> (ConvIdsPage
    -> MultiTablePagingState ConversationPagingName LocalOrRemoteTable)
-> ConvIdsPage
-> GetPaginatedConversationIds
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConvIdsPage
-> MultiTablePagingState ConversationPagingName LocalOrRemoteTable
forall (name :: Symbol) (resultsKey :: Symbol) tables a.
MultiTablePage name resultsKey tables a
-> MultiTablePagingState name tables
MTP.mtpPagingState (ConvIdsPage -> GetPaginatedConversationIds)
-> ConvIdsPage -> GetPaginatedConversationIds
forall a b. (a -> b) -> a -> b
$ ConvIdsPage
page)
          [EJPDConvInfo]
morePages <- QualifiedWithTag 'QLocal UserId
-> ConvIdsPage -> Sem r [EJPDConvInfo]
getPages QualifiedWithTag 'QLocal UserId
luid ConvIdsPage
newPage
          [EJPDConvInfo] -> Sem r [EJPDConvInfo]
forall a. a -> Sem r a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([EJPDConvInfo] -> Sem r [EJPDConvInfo])
-> [EJPDConvInfo] -> Sem r [EJPDConvInfo]
forall a b. (a -> b) -> a -> b
$ [EJPDConvInfo]
renderedPage [EJPDConvInfo] -> [EJPDConvInfo] -> [EJPDConvInfo]
forall a. Semigroup a => a -> a -> a
<> [EJPDConvInfo]
morePages
        else [EJPDConvInfo] -> Sem r [EJPDConvInfo]
forall a. a -> Sem r a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [EJPDConvInfo]
renderedPage

federationAPI :: API IFederationAPI GalleyEffects
federationAPI :: API IFederationAPI GalleyEffects
federationAPI =
  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-federation-status" ((RemoteDomains
 -> Sem
      '[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]
      FederationStatus)
-> QualifiedWithTag 'QLocal UserId
-> RemoteDomains
-> Sem
     '[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]
     FederationStatus
forall a b. a -> b -> a
const RemoteDomains
-> Sem
     '[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]
     FederationStatus
forall (r :: EffectRow).
(Member (Error UnreachableBackends) r, Member FederatorAccess r) =>
RemoteDomains -> Sem r FederationStatus
getFederationStatus)

conversationAPI :: API IConversationAPI GalleyEffects
conversationAPI :: API IConversationAPI 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 @"conversation-get-member" ServerT
  ("conversations"
   :> (Capture "cnv" ConvId
       :> ("members"
           :> (Capture "usr" UserId :> Get '[JSON] (Maybe Member)))))
  (Sem
     (Append
        (DeclaredErrorEffects
           ("conversations"
            :> (Capture "cnv" ConvId
                :> ("members"
                    :> (Capture "usr" UserId :> 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]))
ConvId
-> 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]
     (Maybe Member)
forall (r :: EffectRow).
(Member ConversationStore r, Member (Input (Local ())) r,
 Member MemberStore r) =>
ConvId -> UserId -> Sem r (Maybe Member)
Query.internalGetMember
    API
  (Named
     "conversation-get-member"
     ("conversations"
      :> (Capture "cnv" ConvId
          :> ("members"
              :> (Capture "usr" UserId :> 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
        "conversation-accept-v2"
        (CanThrow 'InvalidOperation
         :> (CanThrow 'ConvNotFound
             :> (ZLocalUser
                 :> (ZOptConn
                     :> ("conversations"
                         :> (Capture "cnv" ConvId
                             :> ("accept" :> ("v2" :> Put '[JSON] Conversation))))))))
      :<|> (Named
              "conversation-block-unqualified"
              (CanThrow 'InvalidOperation
               :> (CanThrow 'ConvNotFound
                   :> (ZUser
                       :> ("conversations"
                           :> (Capture "cnv" ConvId :> ("block" :> Put '[JSON] ()))))))
            :<|> (Named
                    "conversation-block"
                    (CanThrow 'InvalidOperation
                     :> (CanThrow 'ConvNotFound
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> (QualifiedCapture "cnv" ConvId
                                     :> ("block" :> Put '[JSON] ()))))))
                  :<|> (Named
                          "conversation-unblock-unqualified"
                          (CanThrow 'InvalidOperation
                           :> (CanThrow 'ConvNotFound
                               :> (ZLocalUser
                                   :> (ZOptConn
                                       :> ("conversations"
                                           :> (Capture "cnv" ConvId
                                               :> ("unblock" :> Put '[JSON] Conversation)))))))
                        :<|> (Named
                                "conversation-unblock"
                                (CanThrow 'InvalidOperation
                                 :> (CanThrow 'ConvNotFound
                                     :> (ZLocalUser
                                         :> (ZOptConn
                                             :> ("conversations"
                                                 :> (QualifiedCapture "cnv" ConvId
                                                     :> ("unblock" :> Put '[JSON] ())))))))
                              :<|> (Named
                                      "conversation-meta"
                                      (CanThrow 'ConvNotFound
                                       :> ("conversations"
                                           :> (Capture "cnv" ConvId
                                               :> ("meta" :> Get '[JSON] ConversationMetadata))))
                                    :<|> (Named
                                            "conversation-mls-one-to-one"
                                            (CanThrow 'NotConnected
                                             :> (CanThrow 'MLSNotEnabled
                                                 :> ("conversations"
                                                     :> ("mls-one2one"
                                                         :> (ZLocalUser
                                                             :> (QualifiedCapture "user" UserId
                                                                 :> Get '[JSON] Conversation))))))
                                          :<|> Named
                                                 "conversation-mls-one-to-one-established"
                                                 (CanThrow 'NotConnected
                                                  :> (CanThrow 'MLSNotEnabled
                                                      :> (ZLocalUser
                                                          :> ("conversations"
                                                              :> ("mls-one2one"
                                                                  :> (QualifiedCapture "user" UserId
                                                                      :> ("established"
                                                                          :> Get
                                                                               '[JSON]
                                                                               Bool))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
     IConversationAPI
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"conversation-accept-v2" ServerT
  (CanThrow 'InvalidOperation
   :> (CanThrow 'ConvNotFound
       :> (ZLocalUser
           :> (ZOptConn
               :> ("conversations"
                   :> (Capture "cnv" ConvId
                       :> ("accept" :> ("v2" :> Put '[JSON] Conversation))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (CanThrow 'InvalidOperation
            :> (CanThrow 'ConvNotFound
                :> (ZLocalUser
                    :> (ZOptConn
                        :> ("conversations"
                            :> (Capture "cnv" ConvId
                                :> ("accept" :> ("v2" :> Put '[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]))
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> ConvId
-> Sem
     '[Error (Tagged 'InvalidOperation ()),
       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]
     Conversation
forall (r :: EffectRow).
(Member ConversationStore r, Member (Error InternalError) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member NotificationSubsystem r, Member (Input UTCTime) r,
 Member MemberStore r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId -> ConvId -> Sem r Conversation
Update.acceptConv
    API
  (Named
     "conversation-accept-v2"
     (CanThrow 'InvalidOperation
      :> (CanThrow 'ConvNotFound
          :> (ZLocalUser
              :> (ZOptConn
                  :> ("conversations"
                      :> (Capture "cnv" ConvId
                          :> ("accept" :> ("v2" :> Put '[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
        "conversation-block-unqualified"
        (CanThrow 'InvalidOperation
         :> (CanThrow 'ConvNotFound
             :> (ZUser
                 :> ("conversations"
                     :> (Capture "cnv" ConvId :> ("block" :> Put '[JSON] ()))))))
      :<|> (Named
              "conversation-block"
              (CanThrow 'InvalidOperation
               :> (CanThrow 'ConvNotFound
                   :> (ZLocalUser
                       :> ("conversations"
                           :> (QualifiedCapture "cnv" ConvId
                               :> ("block" :> Put '[JSON] ()))))))
            :<|> (Named
                    "conversation-unblock-unqualified"
                    (CanThrow 'InvalidOperation
                     :> (CanThrow 'ConvNotFound
                         :> (ZLocalUser
                             :> (ZOptConn
                                 :> ("conversations"
                                     :> (Capture "cnv" ConvId
                                         :> ("unblock" :> Put '[JSON] Conversation)))))))
                  :<|> (Named
                          "conversation-unblock"
                          (CanThrow 'InvalidOperation
                           :> (CanThrow 'ConvNotFound
                               :> (ZLocalUser
                                   :> (ZOptConn
                                       :> ("conversations"
                                           :> (QualifiedCapture "cnv" ConvId
                                               :> ("unblock" :> Put '[JSON] ())))))))
                        :<|> (Named
                                "conversation-meta"
                                (CanThrow 'ConvNotFound
                                 :> ("conversations"
                                     :> (Capture "cnv" ConvId
                                         :> ("meta" :> Get '[JSON] ConversationMetadata))))
                              :<|> (Named
                                      "conversation-mls-one-to-one"
                                      (CanThrow 'NotConnected
                                       :> (CanThrow 'MLSNotEnabled
                                           :> ("conversations"
                                               :> ("mls-one2one"
                                                   :> (ZLocalUser
                                                       :> (QualifiedCapture "user" UserId
                                                           :> Get '[JSON] Conversation))))))
                                    :<|> Named
                                           "conversation-mls-one-to-one-established"
                                           (CanThrow 'NotConnected
                                            :> (CanThrow 'MLSNotEnabled
                                                :> (ZLocalUser
                                                    :> ("conversations"
                                                        :> ("mls-one2one"
                                                            :> (QualifiedCapture "user" UserId
                                                                :> ("established"
                                                                    :> Get '[JSON] Bool)))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "conversation-accept-v2"
        (CanThrow 'InvalidOperation
         :> (CanThrow 'ConvNotFound
             :> (ZLocalUser
                 :> (ZOptConn
                     :> ("conversations"
                         :> (Capture "cnv" ConvId
                             :> ("accept" :> ("v2" :> Put '[JSON] Conversation))))))))
      :<|> (Named
              "conversation-block-unqualified"
              (CanThrow 'InvalidOperation
               :> (CanThrow 'ConvNotFound
                   :> (ZUser
                       :> ("conversations"
                           :> (Capture "cnv" ConvId :> ("block" :> Put '[JSON] ()))))))
            :<|> (Named
                    "conversation-block"
                    (CanThrow 'InvalidOperation
                     :> (CanThrow 'ConvNotFound
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> (QualifiedCapture "cnv" ConvId
                                     :> ("block" :> Put '[JSON] ()))))))
                  :<|> (Named
                          "conversation-unblock-unqualified"
                          (CanThrow 'InvalidOperation
                           :> (CanThrow 'ConvNotFound
                               :> (ZLocalUser
                                   :> (ZOptConn
                                       :> ("conversations"
                                           :> (Capture "cnv" ConvId
                                               :> ("unblock" :> Put '[JSON] Conversation)))))))
                        :<|> (Named
                                "conversation-unblock"
                                (CanThrow 'InvalidOperation
                                 :> (CanThrow 'ConvNotFound
                                     :> (ZLocalUser
                                         :> (ZOptConn
                                             :> ("conversations"
                                                 :> (QualifiedCapture "cnv" ConvId
                                                     :> ("unblock" :> Put '[JSON] ())))))))
                              :<|> (Named
                                      "conversation-meta"
                                      (CanThrow 'ConvNotFound
                                       :> ("conversations"
                                           :> (Capture "cnv" ConvId
                                               :> ("meta" :> Get '[JSON] ConversationMetadata))))
                                    :<|> (Named
                                            "conversation-mls-one-to-one"
                                            (CanThrow 'NotConnected
                                             :> (CanThrow 'MLSNotEnabled
                                                 :> ("conversations"
                                                     :> ("mls-one2one"
                                                         :> (ZLocalUser
                                                             :> (QualifiedCapture "user" UserId
                                                                 :> Get '[JSON] Conversation))))))
                                          :<|> Named
                                                 "conversation-mls-one-to-one-established"
                                                 (CanThrow 'NotConnected
                                                  :> (CanThrow 'MLSNotEnabled
                                                      :> (ZLocalUser
                                                          :> ("conversations"
                                                              :> ("mls-one2one"
                                                                  :> (QualifiedCapture "user" UserId
                                                                      :> ("established"
                                                                          :> Get
                                                                               '[JSON]
                                                                               Bool))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"conversation-block-unqualified" ServerT
  (CanThrow 'InvalidOperation
   :> (CanThrow 'ConvNotFound
       :> (ZUser
           :> ("conversations"
               :> (Capture "cnv" ConvId :> ("block" :> Put '[JSON] ()))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (CanThrow 'InvalidOperation
            :> (CanThrow 'ConvNotFound
                :> (ZUser
                    :> ("conversations"
                        :> (Capture "cnv" ConvId :> ("block" :> Put '[JSON] ())))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (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 'InvalidOperation ()),
       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 (Error (Tagged 'InvalidOperation ())) r,
 Member MemberStore r) =>
UserId -> ConvId -> Sem r ()
Update.blockConvUnqualified
    API
  (Named
     "conversation-block-unqualified"
     (CanThrow 'InvalidOperation
      :> (CanThrow 'ConvNotFound
          :> (ZUser
              :> ("conversations"
                  :> (Capture "cnv" ConvId :> ("block" :> Put '[JSON] ())))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "conversation-block"
        (CanThrow 'InvalidOperation
         :> (CanThrow 'ConvNotFound
             :> (ZLocalUser
                 :> ("conversations"
                     :> (QualifiedCapture "cnv" ConvId
                         :> ("block" :> Put '[JSON] ()))))))
      :<|> (Named
              "conversation-unblock-unqualified"
              (CanThrow 'InvalidOperation
               :> (CanThrow 'ConvNotFound
                   :> (ZLocalUser
                       :> (ZOptConn
                           :> ("conversations"
                               :> (Capture "cnv" ConvId
                                   :> ("unblock" :> Put '[JSON] Conversation)))))))
            :<|> (Named
                    "conversation-unblock"
                    (CanThrow 'InvalidOperation
                     :> (CanThrow 'ConvNotFound
                         :> (ZLocalUser
                             :> (ZOptConn
                                 :> ("conversations"
                                     :> (QualifiedCapture "cnv" ConvId
                                         :> ("unblock" :> Put '[JSON] ())))))))
                  :<|> (Named
                          "conversation-meta"
                          (CanThrow 'ConvNotFound
                           :> ("conversations"
                               :> (Capture "cnv" ConvId
                                   :> ("meta" :> Get '[JSON] ConversationMetadata))))
                        :<|> (Named
                                "conversation-mls-one-to-one"
                                (CanThrow 'NotConnected
                                 :> (CanThrow 'MLSNotEnabled
                                     :> ("conversations"
                                         :> ("mls-one2one"
                                             :> (ZLocalUser
                                                 :> (QualifiedCapture "user" UserId
                                                     :> Get '[JSON] Conversation))))))
                              :<|> Named
                                     "conversation-mls-one-to-one-established"
                                     (CanThrow 'NotConnected
                                      :> (CanThrow 'MLSNotEnabled
                                          :> (ZLocalUser
                                              :> ("conversations"
                                                  :> ("mls-one2one"
                                                      :> (QualifiedCapture "user" UserId
                                                          :> ("established"
                                                              :> Get '[JSON] Bool))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "conversation-block-unqualified"
        (CanThrow 'InvalidOperation
         :> (CanThrow 'ConvNotFound
             :> (ZUser
                 :> ("conversations"
                     :> (Capture "cnv" ConvId :> ("block" :> Put '[JSON] ()))))))
      :<|> (Named
              "conversation-block"
              (CanThrow 'InvalidOperation
               :> (CanThrow 'ConvNotFound
                   :> (ZLocalUser
                       :> ("conversations"
                           :> (QualifiedCapture "cnv" ConvId
                               :> ("block" :> Put '[JSON] ()))))))
            :<|> (Named
                    "conversation-unblock-unqualified"
                    (CanThrow 'InvalidOperation
                     :> (CanThrow 'ConvNotFound
                         :> (ZLocalUser
                             :> (ZOptConn
                                 :> ("conversations"
                                     :> (Capture "cnv" ConvId
                                         :> ("unblock" :> Put '[JSON] Conversation)))))))
                  :<|> (Named
                          "conversation-unblock"
                          (CanThrow 'InvalidOperation
                           :> (CanThrow 'ConvNotFound
                               :> (ZLocalUser
                                   :> (ZOptConn
                                       :> ("conversations"
                                           :> (QualifiedCapture "cnv" ConvId
                                               :> ("unblock" :> Put '[JSON] ())))))))
                        :<|> (Named
                                "conversation-meta"
                                (CanThrow 'ConvNotFound
                                 :> ("conversations"
                                     :> (Capture "cnv" ConvId
                                         :> ("meta" :> Get '[JSON] ConversationMetadata))))
                              :<|> (Named
                                      "conversation-mls-one-to-one"
                                      (CanThrow 'NotConnected
                                       :> (CanThrow 'MLSNotEnabled
                                           :> ("conversations"
                                               :> ("mls-one2one"
                                                   :> (ZLocalUser
                                                       :> (QualifiedCapture "user" UserId
                                                           :> Get '[JSON] Conversation))))))
                                    :<|> Named
                                           "conversation-mls-one-to-one-established"
                                           (CanThrow 'NotConnected
                                            :> (CanThrow 'MLSNotEnabled
                                                :> (ZLocalUser
                                                    :> ("conversations"
                                                        :> ("mls-one2one"
                                                            :> (QualifiedCapture "user" UserId
                                                                :> ("established"
                                                                    :> Get '[JSON] Bool)))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"conversation-block" ServerT
  (CanThrow 'InvalidOperation
   :> (CanThrow 'ConvNotFound
       :> (ZLocalUser
           :> ("conversations"
               :> (QualifiedCapture "cnv" ConvId
                   :> ("block" :> Put '[JSON] ()))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (CanThrow 'InvalidOperation
            :> (CanThrow 'ConvNotFound
                :> (ZLocalUser
                    :> ("conversations"
                        :> (QualifiedCapture "cnv" ConvId
                            :> ("block" :> Put '[JSON] ())))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (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
-> Sem
     '[Error (Tagged 'InvalidOperation ()),
       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 (Error (Tagged 'InvalidOperation ())) r,
 Member MemberStore r) =>
QualifiedWithTag 'QLocal UserId -> Qualified ConvId -> Sem r ()
Update.blockConv
    API
  (Named
     "conversation-block"
     (CanThrow 'InvalidOperation
      :> (CanThrow 'ConvNotFound
          :> (ZLocalUser
              :> ("conversations"
                  :> (QualifiedCapture "cnv" ConvId
                      :> ("block" :> Put '[JSON] ())))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "conversation-unblock-unqualified"
        (CanThrow 'InvalidOperation
         :> (CanThrow 'ConvNotFound
             :> (ZLocalUser
                 :> (ZOptConn
                     :> ("conversations"
                         :> (Capture "cnv" ConvId
                             :> ("unblock" :> Put '[JSON] Conversation)))))))
      :<|> (Named
              "conversation-unblock"
              (CanThrow 'InvalidOperation
               :> (CanThrow 'ConvNotFound
                   :> (ZLocalUser
                       :> (ZOptConn
                           :> ("conversations"
                               :> (QualifiedCapture "cnv" ConvId
                                   :> ("unblock" :> Put '[JSON] ())))))))
            :<|> (Named
                    "conversation-meta"
                    (CanThrow 'ConvNotFound
                     :> ("conversations"
                         :> (Capture "cnv" ConvId
                             :> ("meta" :> Get '[JSON] ConversationMetadata))))
                  :<|> (Named
                          "conversation-mls-one-to-one"
                          (CanThrow 'NotConnected
                           :> (CanThrow 'MLSNotEnabled
                               :> ("conversations"
                                   :> ("mls-one2one"
                                       :> (ZLocalUser
                                           :> (QualifiedCapture "user" UserId
                                               :> Get '[JSON] Conversation))))))
                        :<|> Named
                               "conversation-mls-one-to-one-established"
                               (CanThrow 'NotConnected
                                :> (CanThrow 'MLSNotEnabled
                                    :> (ZLocalUser
                                        :> ("conversations"
                                            :> ("mls-one2one"
                                                :> (QualifiedCapture "user" UserId
                                                    :> ("established" :> Get '[JSON] Bool)))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "conversation-block"
        (CanThrow 'InvalidOperation
         :> (CanThrow 'ConvNotFound
             :> (ZLocalUser
                 :> ("conversations"
                     :> (QualifiedCapture "cnv" ConvId
                         :> ("block" :> Put '[JSON] ()))))))
      :<|> (Named
              "conversation-unblock-unqualified"
              (CanThrow 'InvalidOperation
               :> (CanThrow 'ConvNotFound
                   :> (ZLocalUser
                       :> (ZOptConn
                           :> ("conversations"
                               :> (Capture "cnv" ConvId
                                   :> ("unblock" :> Put '[JSON] Conversation)))))))
            :<|> (Named
                    "conversation-unblock"
                    (CanThrow 'InvalidOperation
                     :> (CanThrow 'ConvNotFound
                         :> (ZLocalUser
                             :> (ZOptConn
                                 :> ("conversations"
                                     :> (QualifiedCapture "cnv" ConvId
                                         :> ("unblock" :> Put '[JSON] ())))))))
                  :<|> (Named
                          "conversation-meta"
                          (CanThrow 'ConvNotFound
                           :> ("conversations"
                               :> (Capture "cnv" ConvId
                                   :> ("meta" :> Get '[JSON] ConversationMetadata))))
                        :<|> (Named
                                "conversation-mls-one-to-one"
                                (CanThrow 'NotConnected
                                 :> (CanThrow 'MLSNotEnabled
                                     :> ("conversations"
                                         :> ("mls-one2one"
                                             :> (ZLocalUser
                                                 :> (QualifiedCapture "user" UserId
                                                     :> Get '[JSON] Conversation))))))
                              :<|> Named
                                     "conversation-mls-one-to-one-established"
                                     (CanThrow 'NotConnected
                                      :> (CanThrow 'MLSNotEnabled
                                          :> (ZLocalUser
                                              :> ("conversations"
                                                  :> ("mls-one2one"
                                                      :> (QualifiedCapture "user" UserId
                                                          :> ("established"
                                                              :> Get '[JSON] Bool))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"conversation-unblock-unqualified" ServerT
  (CanThrow 'InvalidOperation
   :> (CanThrow 'ConvNotFound
       :> (ZLocalUser
           :> (ZOptConn
               :> ("conversations"
                   :> (Capture "cnv" ConvId
                       :> ("unblock" :> Put '[JSON] Conversation)))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (CanThrow 'InvalidOperation
            :> (CanThrow 'ConvNotFound
                :> (ZLocalUser
                    :> (ZOptConn
                        :> ("conversations"
                            :> (Capture "cnv" ConvId
                                :> ("unblock" :> Put '[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]))
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> ConvId
-> Sem
     '[Error (Tagged 'InvalidOperation ()),
       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]
     Conversation
forall (r :: EffectRow).
(Member ConversationStore r, Member (Error InternalError) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member NotificationSubsystem r, Member (Input UTCTime) r,
 Member MemberStore r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId -> ConvId -> Sem r Conversation
Update.unblockConvUnqualified
    API
  (Named
     "conversation-unblock-unqualified"
     (CanThrow 'InvalidOperation
      :> (CanThrow 'ConvNotFound
          :> (ZLocalUser
              :> (ZOptConn
                  :> ("conversations"
                      :> (Capture "cnv" ConvId
                          :> ("unblock" :> Put '[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
        "conversation-unblock"
        (CanThrow 'InvalidOperation
         :> (CanThrow 'ConvNotFound
             :> (ZLocalUser
                 :> (ZOptConn
                     :> ("conversations"
                         :> (QualifiedCapture "cnv" ConvId
                             :> ("unblock" :> Put '[JSON] ())))))))
      :<|> (Named
              "conversation-meta"
              (CanThrow 'ConvNotFound
               :> ("conversations"
                   :> (Capture "cnv" ConvId
                       :> ("meta" :> Get '[JSON] ConversationMetadata))))
            :<|> (Named
                    "conversation-mls-one-to-one"
                    (CanThrow 'NotConnected
                     :> (CanThrow 'MLSNotEnabled
                         :> ("conversations"
                             :> ("mls-one2one"
                                 :> (ZLocalUser
                                     :> (QualifiedCapture "user" UserId
                                         :> Get '[JSON] Conversation))))))
                  :<|> Named
                         "conversation-mls-one-to-one-established"
                         (CanThrow 'NotConnected
                          :> (CanThrow 'MLSNotEnabled
                              :> (ZLocalUser
                                  :> ("conversations"
                                      :> ("mls-one2one"
                                          :> (QualifiedCapture "user" UserId
                                              :> ("established" :> Get '[JSON] Bool))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "conversation-unblock-unqualified"
        (CanThrow 'InvalidOperation
         :> (CanThrow 'ConvNotFound
             :> (ZLocalUser
                 :> (ZOptConn
                     :> ("conversations"
                         :> (Capture "cnv" ConvId
                             :> ("unblock" :> Put '[JSON] Conversation)))))))
      :<|> (Named
              "conversation-unblock"
              (CanThrow 'InvalidOperation
               :> (CanThrow 'ConvNotFound
                   :> (ZLocalUser
                       :> (ZOptConn
                           :> ("conversations"
                               :> (QualifiedCapture "cnv" ConvId
                                   :> ("unblock" :> Put '[JSON] ())))))))
            :<|> (Named
                    "conversation-meta"
                    (CanThrow 'ConvNotFound
                     :> ("conversations"
                         :> (Capture "cnv" ConvId
                             :> ("meta" :> Get '[JSON] ConversationMetadata))))
                  :<|> (Named
                          "conversation-mls-one-to-one"
                          (CanThrow 'NotConnected
                           :> (CanThrow 'MLSNotEnabled
                               :> ("conversations"
                                   :> ("mls-one2one"
                                       :> (ZLocalUser
                                           :> (QualifiedCapture "user" UserId
                                               :> Get '[JSON] Conversation))))))
                        :<|> Named
                               "conversation-mls-one-to-one-established"
                               (CanThrow 'NotConnected
                                :> (CanThrow 'MLSNotEnabled
                                    :> (ZLocalUser
                                        :> ("conversations"
                                            :> ("mls-one2one"
                                                :> (QualifiedCapture "user" UserId
                                                    :> ("established" :> Get '[JSON] Bool)))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"conversation-unblock" ServerT
  (CanThrow 'InvalidOperation
   :> (CanThrow 'ConvNotFound
       :> (ZLocalUser
           :> (ZOptConn
               :> ("conversations"
                   :> (QualifiedCapture "cnv" ConvId
                       :> ("unblock" :> Put '[JSON] ())))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (CanThrow 'InvalidOperation
            :> (CanThrow 'ConvNotFound
                :> (ZLocalUser
                    :> (ZOptConn
                        :> ("conversations"
                            :> (QualifiedCapture "cnv" ConvId
                                :> ("unblock" :> Put '[JSON] ()))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (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 ConnId
-> Qualified ConvId
-> Sem
     '[Error (Tagged 'InvalidOperation ()),
       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 InternalError) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member NotificationSubsystem r, Member (Input UTCTime) r,
 Member MemberStore r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId -> Qualified ConvId -> Sem r ()
Update.unblockConv
    API
  (Named
     "conversation-unblock"
     (CanThrow 'InvalidOperation
      :> (CanThrow 'ConvNotFound
          :> (ZLocalUser
              :> (ZOptConn
                  :> ("conversations"
                      :> (QualifiedCapture "cnv" ConvId
                          :> ("unblock" :> Put '[JSON] ()))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "conversation-meta"
        (CanThrow 'ConvNotFound
         :> ("conversations"
             :> (Capture "cnv" ConvId
                 :> ("meta" :> Get '[JSON] ConversationMetadata))))
      :<|> (Named
              "conversation-mls-one-to-one"
              (CanThrow 'NotConnected
               :> (CanThrow 'MLSNotEnabled
                   :> ("conversations"
                       :> ("mls-one2one"
                           :> (ZLocalUser
                               :> (QualifiedCapture "user" UserId
                                   :> Get '[JSON] Conversation))))))
            :<|> Named
                   "conversation-mls-one-to-one-established"
                   (CanThrow 'NotConnected
                    :> (CanThrow 'MLSNotEnabled
                        :> (ZLocalUser
                            :> ("conversations"
                                :> ("mls-one2one"
                                    :> (QualifiedCapture "user" UserId
                                        :> ("established" :> Get '[JSON] Bool)))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "conversation-unblock"
        (CanThrow 'InvalidOperation
         :> (CanThrow 'ConvNotFound
             :> (ZLocalUser
                 :> (ZOptConn
                     :> ("conversations"
                         :> (QualifiedCapture "cnv" ConvId
                             :> ("unblock" :> Put '[JSON] ())))))))
      :<|> (Named
              "conversation-meta"
              (CanThrow 'ConvNotFound
               :> ("conversations"
                   :> (Capture "cnv" ConvId
                       :> ("meta" :> Get '[JSON] ConversationMetadata))))
            :<|> (Named
                    "conversation-mls-one-to-one"
                    (CanThrow 'NotConnected
                     :> (CanThrow 'MLSNotEnabled
                         :> ("conversations"
                             :> ("mls-one2one"
                                 :> (ZLocalUser
                                     :> (QualifiedCapture "user" UserId
                                         :> Get '[JSON] Conversation))))))
                  :<|> Named
                         "conversation-mls-one-to-one-established"
                         (CanThrow 'NotConnected
                          :> (CanThrow 'MLSNotEnabled
                              :> (ZLocalUser
                                  :> ("conversations"
                                      :> ("mls-one2one"
                                          :> (QualifiedCapture "user" UserId
                                              :> ("established" :> Get '[JSON] Bool))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"conversation-meta" ServerT
  (CanThrow 'ConvNotFound
   :> ("conversations"
       :> (Capture "cnv" ConvId
           :> ("meta" :> Get '[JSON] ConversationMetadata))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (CanThrow 'ConvNotFound
            :> ("conversations"
                :> (Capture "cnv" ConvId
                    :> ("meta" :> Get '[JSON] ConversationMetadata)))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
ConvId
-> 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]
     ConversationMetadata
forall (r :: EffectRow).
(Member ConversationStore r,
 Member (Error (Tagged 'ConvNotFound ())) r) =>
ConvId -> Sem r ConversationMetadata
Query.getConversationMeta
    API
  (Named
     "conversation-meta"
     (CanThrow 'ConvNotFound
      :> ("conversations"
          :> (Capture "cnv" ConvId
              :> ("meta" :> Get '[JSON] ConversationMetadata)))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "conversation-mls-one-to-one"
        (CanThrow 'NotConnected
         :> (CanThrow 'MLSNotEnabled
             :> ("conversations"
                 :> ("mls-one2one"
                     :> (ZLocalUser
                         :> (QualifiedCapture "user" UserId
                             :> Get '[JSON] Conversation))))))
      :<|> Named
             "conversation-mls-one-to-one-established"
             (CanThrow 'NotConnected
              :> (CanThrow 'MLSNotEnabled
                  :> (ZLocalUser
                      :> ("conversations"
                          :> ("mls-one2one"
                              :> (QualifiedCapture "user" UserId
                                  :> ("established" :> Get '[JSON] Bool))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "conversation-meta"
        (CanThrow 'ConvNotFound
         :> ("conversations"
             :> (Capture "cnv" ConvId
                 :> ("meta" :> Get '[JSON] ConversationMetadata))))
      :<|> (Named
              "conversation-mls-one-to-one"
              (CanThrow 'NotConnected
               :> (CanThrow 'MLSNotEnabled
                   :> ("conversations"
                       :> ("mls-one2one"
                           :> (ZLocalUser
                               :> (QualifiedCapture "user" UserId
                                   :> Get '[JSON] Conversation))))))
            :<|> Named
                   "conversation-mls-one-to-one-established"
                   (CanThrow 'NotConnected
                    :> (CanThrow 'MLSNotEnabled
                        :> (ZLocalUser
                            :> ("conversations"
                                :> ("mls-one2one"
                                    :> (QualifiedCapture "user" UserId
                                        :> ("established" :> Get '[JSON] Bool)))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"conversation-mls-one-to-one" ServerT
  (CanThrow 'NotConnected
   :> (CanThrow 'MLSNotEnabled
       :> ("conversations"
           :> ("mls-one2one"
               :> (ZLocalUser
                   :> (QualifiedCapture "user" UserId
                       :> Get '[JSON] Conversation))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (CanThrow 'NotConnected
            :> (CanThrow 'MLSNotEnabled
                :> ("conversations"
                    :> ("mls-one2one"
                        :> (ZLocalUser
                            :> (QualifiedCapture "user" UserId
                                :> 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]))
QualifiedWithTag 'QLocal UserId
-> Qualified UserId
-> Sem
     '[Error (Tagged 'NotConnected ()),
       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 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 Conversation
Query.getMLSOne2OneConversationInternal
    API
  (Named
     "conversation-mls-one-to-one"
     (CanThrow 'NotConnected
      :> (CanThrow 'MLSNotEnabled
          :> ("conversations"
              :> ("mls-one2one"
                  :> (ZLocalUser
                      :> (QualifiedCapture "user" UserId
                          :> 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
        "conversation-mls-one-to-one-established"
        (CanThrow 'NotConnected
         :> (CanThrow 'MLSNotEnabled
             :> (ZLocalUser
                 :> ("conversations"
                     :> ("mls-one2one"
                         :> (QualifiedCapture "user" UserId
                             :> ("established" :> Get '[JSON] Bool))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "conversation-mls-one-to-one"
        (CanThrow 'NotConnected
         :> (CanThrow 'MLSNotEnabled
             :> ("conversations"
                 :> ("mls-one2one"
                     :> (ZLocalUser
                         :> (QualifiedCapture "user" UserId
                             :> Get '[JSON] Conversation))))))
      :<|> Named
             "conversation-mls-one-to-one-established"
             (CanThrow 'NotConnected
              :> (CanThrow 'MLSNotEnabled
                  :> (ZLocalUser
                      :> ("conversations"
                          :> ("mls-one2one"
                              :> (QualifiedCapture "user" UserId
                                  :> ("established" :> Get '[JSON] Bool))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"conversation-mls-one-to-one-established" ServerT
  (CanThrow 'NotConnected
   :> (CanThrow 'MLSNotEnabled
       :> (ZLocalUser
           :> ("conversations"
               :> ("mls-one2one"
                   :> (QualifiedCapture "user" UserId
                       :> ("established" :> Get '[JSON] Bool)))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (CanThrow 'NotConnected
            :> (CanThrow 'MLSNotEnabled
                :> (ZLocalUser
                    :> ("conversations"
                        :> ("mls-one2one"
                            :> (QualifiedCapture "user" UserId
                                :> ("established" :> Get '[JSON] Bool))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (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 'NotConnected ()),
       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]
     Bool
forall (r :: EffectRow).
(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 (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId -> Qualified UserId -> Sem r Bool
Query.isMLSOne2OneEstablished

legalholdWhitelistedTeamsAPI :: API ILegalholdWhitelistedTeamsAPI GalleyEffects
legalholdWhitelistedTeamsAPI :: API ILegalholdWhitelistedTeamsAPI GalleyEffects
legalholdWhitelistedTeamsAPI = ServerT
  ILegalholdWhitelistedTeamsAPI
  (Sem
     (Append
        (DeclaredErrorEffects ILegalholdWhitelistedTeamsAPI)
        GalleyEffects))
-> API ILegalholdWhitelistedTeamsAPI GalleyEffects
forall (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API api r0
mkAPI (ServerT
   ILegalholdWhitelistedTeamsAPI
   (Sem
      (Append
         (DeclaredErrorEffects ILegalholdWhitelistedTeamsAPI)
         GalleyEffects))
 -> API ILegalholdWhitelistedTeamsAPI GalleyEffects)
-> ServerT
     ILegalholdWhitelistedTeamsAPI
     (Sem
        (Append
           (DeclaredErrorEffects ILegalholdWhitelistedTeamsAPI)
           GalleyEffects))
-> API ILegalholdWhitelistedTeamsAPI GalleyEffects
forall a b. (a -> b) -> a -> b
$ \TeamId
tid -> (forall x.
 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]
   x
 -> 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]
      x)
-> API
     (Named
        "set-team-legalhold-whitelisted"
        (MultiVerb
           'PUT '[JSON] '[RespondEmpty 200 "Team Legalhold Whitelisted"] ())
      :<|> (Named
              "unset-team-legalhold-whitelisted"
              (MultiVerb
                 'DELETE
                 '[JSON]
                 '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
                 ())
            :<|> Named
                   "get-team-legalhold-whitelisted"
                   (MultiVerb
                      'GET
                      '[JSON]
                      '[RespondEmpty 404 "Team not Legalhold Whitelisted",
                        RespondEmpty 200 "Team Legalhold Whitelisted"]
                      Bool)))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> ServerT
     (Named
        "set-team-legalhold-whitelisted"
        (MultiVerb
           'PUT '[JSON] '[RespondEmpty 200 "Team Legalhold Whitelisted"] ())
      :<|> (Named
              "unset-team-legalhold-whitelisted"
              (MultiVerb
                 'DELETE
                 '[JSON]
                 '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
                 ())
            :<|> Named
                   "get-team-legalhold-whitelisted"
                   (MultiVerb
                      'GET
                      '[JSON]
                      '[RespondEmpty 404 "Team not Legalhold Whitelisted",
                        RespondEmpty 200 "Team Legalhold Whitelisted"]
                      Bool)))
     (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])
forall {k} (api :: k) (r :: EffectRow) (n :: * -> *).
HasServer api '[Domain] =>
(forall x. Sem r x -> n x) -> API api r -> ServerT api n
hoistAPIHandler 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]
  x
-> 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]
     x
forall a. a -> a
forall x.
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]
  x
-> 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]
     x
Imports.id (TeamId -> API ILegalholdWhitelistedTeamsAPIBase GalleyEffects
base TeamId
tid)
  where
    base :: TeamId -> API ILegalholdWhitelistedTeamsAPIBase GalleyEffects
    base :: TeamId -> API ILegalholdWhitelistedTeamsAPIBase GalleyEffects
base TeamId
tid =
      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 @"set-team-legalhold-whitelisted" (TeamId
-> 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]
     ()
forall (r :: EffectRow).
Member LegalHoldStore r =>
TeamId -> Sem r ()
LegalHoldStore.setTeamLegalholdWhitelisted TeamId
tid)
        API
  (Named
     "set-team-legalhold-whitelisted"
     (MultiVerb
        'PUT '[JSON] '[RespondEmpty 200 "Team Legalhold Whitelisted"] ()))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "unset-team-legalhold-whitelisted"
        (MultiVerb
           'DELETE
           '[JSON]
           '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
           ())
      :<|> Named
             "get-team-legalhold-whitelisted"
             (MultiVerb
                'GET
                '[JSON]
                '[RespondEmpty 404 "Team not Legalhold Whitelisted",
                  RespondEmpty 200 "Team Legalhold Whitelisted"]
                Bool))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "set-team-legalhold-whitelisted"
        (MultiVerb
           'PUT '[JSON] '[RespondEmpty 200 "Team Legalhold Whitelisted"] ())
      :<|> (Named
              "unset-team-legalhold-whitelisted"
              (MultiVerb
                 'DELETE
                 '[JSON]
                 '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
                 ())
            :<|> Named
                   "get-team-legalhold-whitelisted"
                   (MultiVerb
                      'GET
                      '[JSON]
                      '[RespondEmpty 404 "Team not Legalhold Whitelisted",
                        RespondEmpty 200 "Team Legalhold Whitelisted"]
                      Bool)))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"unset-team-legalhold-whitelisted" (TeamId
-> 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]
     ()
forall (r :: EffectRow).
Member LegalHoldStore r =>
TeamId -> Sem r ()
unsetTeamLegalholdWhitelistedH TeamId
tid)
        API
  (Named
     "unset-team-legalhold-whitelisted"
     (MultiVerb
        'DELETE
        '[JSON]
        '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
        ()))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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-team-legalhold-whitelisted"
        (MultiVerb
           'GET
           '[JSON]
           '[RespondEmpty 404 "Team not Legalhold Whitelisted",
             RespondEmpty 200 "Team Legalhold Whitelisted"]
           Bool))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "unset-team-legalhold-whitelisted"
        (MultiVerb
           'DELETE
           '[JSON]
           '[RespondEmpty 204 "Team Legalhold un-Whitelisted"]
           ())
      :<|> Named
             "get-team-legalhold-whitelisted"
             (MultiVerb
                'GET
                '[JSON]
                '[RespondEmpty 404 "Team not Legalhold Whitelisted",
                  RespondEmpty 200 "Team Legalhold Whitelisted"]
                Bool))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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-team-legalhold-whitelisted" (TeamId
-> 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]
     Bool
forall (r :: EffectRow).
Member LegalHoldStore r =>
TeamId -> Sem r Bool
LegalHoldStore.isTeamLegalholdWhitelisted TeamId
tid)

iTeamsAPI :: API ITeamsAPI GalleyEffects
iTeamsAPI :: API ITeamsAPI GalleyEffects
iTeamsAPI = ServerT
  ITeamsAPI
  (Sem (Append (DeclaredErrorEffects ITeamsAPI) GalleyEffects))
-> API ITeamsAPI GalleyEffects
forall (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API api r0
mkAPI (ServerT
   ITeamsAPI
   (Sem (Append (DeclaredErrorEffects ITeamsAPI) GalleyEffects))
 -> API ITeamsAPI GalleyEffects)
-> ServerT
     ITeamsAPI
     (Sem (Append (DeclaredErrorEffects ITeamsAPI) GalleyEffects))
-> API ITeamsAPI GalleyEffects
forall a b. (a -> b) -> a -> b
$ \TeamId
tid -> (forall x.
 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]
   x
 -> 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]
      x)
-> API
     (Named
        "get-team-internal"
        (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
      :<|> (Named
              "create-binding-team"
              (ZUser
               :> (ReqBody '[JSON] BindingNewTeam
                   :> MultiVerb
                        'PUT
                        '[JSON]
                        '[WithHeaders
                            '[Header "Location" TeamId] TeamId (RespondEmpty 201 "OK")]
                        TeamId))
            :<|> (Named
                    "delete-binding-team"
                    (CanThrow 'NoBindingTeam
                     :> (CanThrow 'NotAOneMemberTeam
                         :> (CanThrow 'DeleteQueueFull
                             :> (CanThrow 'TeamNotFound
                                 :> (QueryFlag "force"
                                     :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 202 "OK"] ())))))
                  :<|> (Named
                          "get-team-name"
                          ("name" :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
                        :<|> (Named
                                "update-team-status"
                                ("status"
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow 'InvalidTeamStatusUpdate
                                         :> (ReqBody '[JSON] TeamStatusUpdate
                                             :> MultiVerb
                                                  'PUT '[JSON] '[RespondEmpty 200 "OK"] ()))))
                              :<|> (("members"
                                     :> (Named
                                           "unchecked-add-team-member"
                                           (CanThrow 'TooManyTeamMembers
                                            :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                                :> (CanThrow 'TooManyTeamAdmins
                                                    :> (ReqBody '[JSON] NewTeamMember
                                                        :> MultiVerb
                                                             'POST
                                                             '[JSON]
                                                             '[RespondEmpty 200 "OK"]
                                                             ()))))
                                         :<|> (Named
                                                 "unchecked-get-team-members"
                                                 (QueryParam'
                                                    '[Strict]
                                                    "maxResults"
                                                    (Range 1 HardTruncationLimit Int32)
                                                  :> Get '[JSON] TeamMemberList)
                                               :<|> (Named
                                                       "unchecked-get-team-member"
                                                       (Capture "uid" UserId
                                                        :> (CanThrow 'TeamMemberNotFound
                                                            :> Get '[JSON] TeamMember))
                                                     :<|> (Named
                                                             "can-user-join-team"
                                                             ("check"
                                                              :> (CanThrow
                                                                    'TooManyTeamMembersOnTeamWithLegalhold
                                                                  :> MultiVerb
                                                                       'GET
                                                                       '[JSON]
                                                                       '[RespondEmpty
                                                                           200 "User can join"]
                                                                       ()))
                                                           :<|> Named
                                                                  "unchecked-update-team-member"
                                                                  (CanThrow 'AccessDenied
                                                                   :> (CanThrow 'InvalidPermissions
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 'TeamMemberNotFound
                                                                               :> (CanThrow
                                                                                     'TooManyTeamAdmins
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 NewTeamMember
                                                                                               :> MultiVerb
                                                                                                    'PUT
                                                                                                    '[JSON]
                                                                                                    '[RespondEmpty
                                                                                                        200
                                                                                                        ""]
                                                                                                    ())))))))))))))
                                    :<|> (Named
                                            "user-is-team-owner"
                                            ("is-team-owner"
                                             :> (Capture "uid" UserId
                                                 :> (CanThrow 'AccessDenied
                                                     :> (CanThrow 'TeamMemberNotFound
                                                         :> (CanThrow 'NotATeamMember
                                                             :> MultiVerb
                                                                  'GET
                                                                  '[JSON]
                                                                  '[RespondEmpty
                                                                      200 "User is team owner"]
                                                                  ())))))
                                          :<|> ("search-visibility"
                                                :> (Named
                                                      "get-search-visibility-internal"
                                                      (Get '[JSON] TeamSearchVisibilityView)
                                                    :<|> Named
                                                           "set-search-visibility-internal"
                                                           (CanThrow 'TeamSearchVisibilityNotEnabled
                                                            :> (CanThrow
                                                                  ('MissingPermission 'Nothing)
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> (ReqBody
                                                                              '[JSON]
                                                                              TeamSearchVisibilityView
                                                                            :> MultiVerb
                                                                                 'PUT
                                                                                 '[JSON]
                                                                                 '[RespondEmpty
                                                                                     204 "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]
-> ServerT
     (Named
        "get-team-internal"
        (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
      :<|> (Named
              "create-binding-team"
              (ZUser
               :> (ReqBody '[JSON] BindingNewTeam
                   :> MultiVerb
                        'PUT
                        '[JSON]
                        '[WithHeaders
                            '[Header "Location" TeamId] TeamId (RespondEmpty 201 "OK")]
                        TeamId))
            :<|> (Named
                    "delete-binding-team"
                    (CanThrow 'NoBindingTeam
                     :> (CanThrow 'NotAOneMemberTeam
                         :> (CanThrow 'DeleteQueueFull
                             :> (CanThrow 'TeamNotFound
                                 :> (QueryFlag "force"
                                     :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 202 "OK"] ())))))
                  :<|> (Named
                          "get-team-name"
                          ("name" :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
                        :<|> (Named
                                "update-team-status"
                                ("status"
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow 'InvalidTeamStatusUpdate
                                         :> (ReqBody '[JSON] TeamStatusUpdate
                                             :> MultiVerb
                                                  'PUT '[JSON] '[RespondEmpty 200 "OK"] ()))))
                              :<|> (("members"
                                     :> (Named
                                           "unchecked-add-team-member"
                                           (CanThrow 'TooManyTeamMembers
                                            :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                                :> (CanThrow 'TooManyTeamAdmins
                                                    :> (ReqBody '[JSON] NewTeamMember
                                                        :> MultiVerb
                                                             'POST
                                                             '[JSON]
                                                             '[RespondEmpty 200 "OK"]
                                                             ()))))
                                         :<|> (Named
                                                 "unchecked-get-team-members"
                                                 (QueryParam'
                                                    '[Strict]
                                                    "maxResults"
                                                    (Range 1 HardTruncationLimit Int32)
                                                  :> Get '[JSON] TeamMemberList)
                                               :<|> (Named
                                                       "unchecked-get-team-member"
                                                       (Capture "uid" UserId
                                                        :> (CanThrow 'TeamMemberNotFound
                                                            :> Get '[JSON] TeamMember))
                                                     :<|> (Named
                                                             "can-user-join-team"
                                                             ("check"
                                                              :> (CanThrow
                                                                    'TooManyTeamMembersOnTeamWithLegalhold
                                                                  :> MultiVerb
                                                                       'GET
                                                                       '[JSON]
                                                                       '[RespondEmpty
                                                                           200 "User can join"]
                                                                       ()))
                                                           :<|> Named
                                                                  "unchecked-update-team-member"
                                                                  (CanThrow 'AccessDenied
                                                                   :> (CanThrow 'InvalidPermissions
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 'TeamMemberNotFound
                                                                               :> (CanThrow
                                                                                     'TooManyTeamAdmins
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 NewTeamMember
                                                                                               :> MultiVerb
                                                                                                    'PUT
                                                                                                    '[JSON]
                                                                                                    '[RespondEmpty
                                                                                                        200
                                                                                                        ""]
                                                                                                    ())))))))))))))
                                    :<|> (Named
                                            "user-is-team-owner"
                                            ("is-team-owner"
                                             :> (Capture "uid" UserId
                                                 :> (CanThrow 'AccessDenied
                                                     :> (CanThrow 'TeamMemberNotFound
                                                         :> (CanThrow 'NotATeamMember
                                                             :> MultiVerb
                                                                  'GET
                                                                  '[JSON]
                                                                  '[RespondEmpty
                                                                      200 "User is team owner"]
                                                                  ())))))
                                          :<|> ("search-visibility"
                                                :> (Named
                                                      "get-search-visibility-internal"
                                                      (Get '[JSON] TeamSearchVisibilityView)
                                                    :<|> Named
                                                           "set-search-visibility-internal"
                                                           (CanThrow 'TeamSearchVisibilityNotEnabled
                                                            :> (CanThrow
                                                                  ('MissingPermission 'Nothing)
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> (ReqBody
                                                                              '[JSON]
                                                                              TeamSearchVisibilityView
                                                                            :> MultiVerb
                                                                                 'PUT
                                                                                 '[JSON]
                                                                                 '[RespondEmpty
                                                                                     204 "OK"]
                                                                                 ()))))))))))))))
     (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])
forall {k} (api :: k) (r :: EffectRow) (n :: * -> *).
HasServer api '[Domain] =>
(forall x. Sem r x -> n x) -> API api r -> ServerT api n
hoistAPIHandler 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]
  x
-> 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]
     x
forall a. a -> a
forall x.
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]
  x
-> 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]
     x
Imports.id (TeamId -> API ITeamsAPIBase GalleyEffects
base TeamId
tid)
  where
    hoistAPISegment ::
      (ServerT (seg :> inner) (Sem r) ~ ServerT inner (Sem r)) =>
      API inner r ->
      API (seg :> inner) r
    hoistAPISegment :: forall {k} (seg :: k) inner (r :: EffectRow).
(ServerT (seg :> inner) (Sem r) ~ ServerT inner (Sem r)) =>
API inner r -> API (seg :> inner) r
hoistAPISegment = (ServerT inner (Sem r) -> ServerT (seg :> inner) (Sem r))
-> API inner r -> API (seg :> inner) r
forall {k1} {k2} (api1 :: k1) (api2 :: k2) (r1 :: EffectRow)
       (r2 :: EffectRow).
(ServerT api1 (Sem r1) -> ServerT api2 (Sem r2))
-> API api1 r1 -> API api2 r2
hoistAPI ServerT inner (Sem r) -> ServerT inner (Sem r)
ServerT inner (Sem r) -> ServerT (seg :> inner) (Sem r)
forall a. a -> a
Imports.id

    base :: TeamId -> API ITeamsAPIBase GalleyEffects
    base :: TeamId -> API ITeamsAPIBase GalleyEffects
base TeamId
tid =
      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-team-internal" (TeamId
-> Sem
     '[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]
     TeamData
forall (r :: EffectRow).
(Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r) =>
TeamId -> Sem r TeamData
Teams.getTeamInternalH TeamId
tid)
        API
  (Named
     "get-team-internal"
     (CanThrow 'TeamNotFound :> Get '[JSON] TeamData))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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-binding-team"
        (ZUser
         :> (ReqBody '[JSON] BindingNewTeam
             :> MultiVerb
                  'PUT
                  '[JSON]
                  '[WithHeaders
                      '[Header "Location" TeamId] TeamId (RespondEmpty 201 "OK")]
                  TeamId))
      :<|> (Named
              "delete-binding-team"
              (CanThrow 'NoBindingTeam
               :> (CanThrow 'NotAOneMemberTeam
                   :> (CanThrow 'DeleteQueueFull
                       :> (CanThrow 'TeamNotFound
                           :> (QueryFlag "force"
                               :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 202 "OK"] ())))))
            :<|> (Named
                    "get-team-name"
                    ("name" :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
                  :<|> (Named
                          "update-team-status"
                          ("status"
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow 'InvalidTeamStatusUpdate
                                   :> (ReqBody '[JSON] TeamStatusUpdate
                                       :> MultiVerb 'PUT '[JSON] '[RespondEmpty 200 "OK"] ()))))
                        :<|> (("members"
                               :> (Named
                                     "unchecked-add-team-member"
                                     (CanThrow 'TooManyTeamMembers
                                      :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                          :> (CanThrow 'TooManyTeamAdmins
                                              :> (ReqBody '[JSON] NewTeamMember
                                                  :> MultiVerb
                                                       'POST '[JSON] '[RespondEmpty 200 "OK"] ()))))
                                   :<|> (Named
                                           "unchecked-get-team-members"
                                           (QueryParam'
                                              '[Strict]
                                              "maxResults"
                                              (Range 1 HardTruncationLimit Int32)
                                            :> Get '[JSON] TeamMemberList)
                                         :<|> (Named
                                                 "unchecked-get-team-member"
                                                 (Capture "uid" UserId
                                                  :> (CanThrow 'TeamMemberNotFound
                                                      :> Get '[JSON] TeamMember))
                                               :<|> (Named
                                                       "can-user-join-team"
                                                       ("check"
                                                        :> (CanThrow
                                                              'TooManyTeamMembersOnTeamWithLegalhold
                                                            :> MultiVerb
                                                                 'GET
                                                                 '[JSON]
                                                                 '[RespondEmpty 200 "User can join"]
                                                                 ()))
                                                     :<|> Named
                                                            "unchecked-update-team-member"
                                                            (CanThrow 'AccessDenied
                                                             :> (CanThrow 'InvalidPermissions
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow
                                                                           'TeamMemberNotFound
                                                                         :> (CanThrow
                                                                               'TooManyTeamAdmins
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           NewTeamMember
                                                                                         :> MultiVerb
                                                                                              'PUT
                                                                                              '[JSON]
                                                                                              '[RespondEmpty
                                                                                                  200
                                                                                                  ""]
                                                                                              ())))))))))))))
                              :<|> (Named
                                      "user-is-team-owner"
                                      ("is-team-owner"
                                       :> (Capture "uid" UserId
                                           :> (CanThrow 'AccessDenied
                                               :> (CanThrow 'TeamMemberNotFound
                                                   :> (CanThrow 'NotATeamMember
                                                       :> MultiVerb
                                                            'GET
                                                            '[JSON]
                                                            '[RespondEmpty 200 "User is team owner"]
                                                            ())))))
                                    :<|> ("search-visibility"
                                          :> (Named
                                                "get-search-visibility-internal"
                                                (Get '[JSON] TeamSearchVisibilityView)
                                              :<|> Named
                                                     "set-search-visibility-internal"
                                                     (CanThrow 'TeamSearchVisibilityNotEnabled
                                                      :> (CanThrow ('MissingPermission 'Nothing)
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> (ReqBody
                                                                        '[JSON]
                                                                        TeamSearchVisibilityView
                                                                      :> MultiVerb
                                                                           'PUT
                                                                           '[JSON]
                                                                           '[RespondEmpty 204 "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
        "get-team-internal"
        (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
      :<|> (Named
              "create-binding-team"
              (ZUser
               :> (ReqBody '[JSON] BindingNewTeam
                   :> MultiVerb
                        'PUT
                        '[JSON]
                        '[WithHeaders
                            '[Header "Location" TeamId] TeamId (RespondEmpty 201 "OK")]
                        TeamId))
            :<|> (Named
                    "delete-binding-team"
                    (CanThrow 'NoBindingTeam
                     :> (CanThrow 'NotAOneMemberTeam
                         :> (CanThrow 'DeleteQueueFull
                             :> (CanThrow 'TeamNotFound
                                 :> (QueryFlag "force"
                                     :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 202 "OK"] ())))))
                  :<|> (Named
                          "get-team-name"
                          ("name" :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
                        :<|> (Named
                                "update-team-status"
                                ("status"
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow 'InvalidTeamStatusUpdate
                                         :> (ReqBody '[JSON] TeamStatusUpdate
                                             :> MultiVerb
                                                  'PUT '[JSON] '[RespondEmpty 200 "OK"] ()))))
                              :<|> (("members"
                                     :> (Named
                                           "unchecked-add-team-member"
                                           (CanThrow 'TooManyTeamMembers
                                            :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                                :> (CanThrow 'TooManyTeamAdmins
                                                    :> (ReqBody '[JSON] NewTeamMember
                                                        :> MultiVerb
                                                             'POST
                                                             '[JSON]
                                                             '[RespondEmpty 200 "OK"]
                                                             ()))))
                                         :<|> (Named
                                                 "unchecked-get-team-members"
                                                 (QueryParam'
                                                    '[Strict]
                                                    "maxResults"
                                                    (Range 1 HardTruncationLimit Int32)
                                                  :> Get '[JSON] TeamMemberList)
                                               :<|> (Named
                                                       "unchecked-get-team-member"
                                                       (Capture "uid" UserId
                                                        :> (CanThrow 'TeamMemberNotFound
                                                            :> Get '[JSON] TeamMember))
                                                     :<|> (Named
                                                             "can-user-join-team"
                                                             ("check"
                                                              :> (CanThrow
                                                                    'TooManyTeamMembersOnTeamWithLegalhold
                                                                  :> MultiVerb
                                                                       'GET
                                                                       '[JSON]
                                                                       '[RespondEmpty
                                                                           200 "User can join"]
                                                                       ()))
                                                           :<|> Named
                                                                  "unchecked-update-team-member"
                                                                  (CanThrow 'AccessDenied
                                                                   :> (CanThrow 'InvalidPermissions
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 'TeamMemberNotFound
                                                                               :> (CanThrow
                                                                                     'TooManyTeamAdmins
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 NewTeamMember
                                                                                               :> MultiVerb
                                                                                                    'PUT
                                                                                                    '[JSON]
                                                                                                    '[RespondEmpty
                                                                                                        200
                                                                                                        ""]
                                                                                                    ())))))))))))))
                                    :<|> (Named
                                            "user-is-team-owner"
                                            ("is-team-owner"
                                             :> (Capture "uid" UserId
                                                 :> (CanThrow 'AccessDenied
                                                     :> (CanThrow 'TeamMemberNotFound
                                                         :> (CanThrow 'NotATeamMember
                                                             :> MultiVerb
                                                                  'GET
                                                                  '[JSON]
                                                                  '[RespondEmpty
                                                                      200 "User is team owner"]
                                                                  ())))))
                                          :<|> ("search-visibility"
                                                :> (Named
                                                      "get-search-visibility-internal"
                                                      (Get '[JSON] TeamSearchVisibilityView)
                                                    :<|> Named
                                                           "set-search-visibility-internal"
                                                           (CanThrow 'TeamSearchVisibilityNotEnabled
                                                            :> (CanThrow
                                                                  ('MissingPermission 'Nothing)
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> (ReqBody
                                                                              '[JSON]
                                                                              TeamSearchVisibilityView
                                                                            :> MultiVerb
                                                                                 'PUT
                                                                                 '[JSON]
                                                                                 '[RespondEmpty
                                                                                     204 "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]
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-binding-team" (TeamId
-> UserId
-> BindingNewTeam
-> 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]
     TeamId
forall (r :: EffectRow).
(Member NotificationSubsystem r, Member (Input UTCTime) r,
 Member TeamStore r) =>
TeamId -> UserId -> BindingNewTeam -> Sem r TeamId
Teams.createBindingTeam TeamId
tid)
        API
  (Named
     "create-binding-team"
     (ZUser
      :> (ReqBody '[JSON] BindingNewTeam
          :> MultiVerb
               'PUT
               '[JSON]
               '[WithHeaders
                   '[Header "Location" TeamId] TeamId (RespondEmpty 201 "OK")]
               TeamId)))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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-binding-team"
        (CanThrow 'NoBindingTeam
         :> (CanThrow 'NotAOneMemberTeam
             :> (CanThrow 'DeleteQueueFull
                 :> (CanThrow 'TeamNotFound
                     :> (QueryFlag "force"
                         :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 202 "OK"] ())))))
      :<|> (Named
              "get-team-name"
              ("name" :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
            :<|> (Named
                    "update-team-status"
                    ("status"
                     :> (CanThrow 'TeamNotFound
                         :> (CanThrow 'InvalidTeamStatusUpdate
                             :> (ReqBody '[JSON] TeamStatusUpdate
                                 :> MultiVerb 'PUT '[JSON] '[RespondEmpty 200 "OK"] ()))))
                  :<|> (("members"
                         :> (Named
                               "unchecked-add-team-member"
                               (CanThrow 'TooManyTeamMembers
                                :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                    :> (CanThrow 'TooManyTeamAdmins
                                        :> (ReqBody '[JSON] NewTeamMember
                                            :> MultiVerb
                                                 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))))
                             :<|> (Named
                                     "unchecked-get-team-members"
                                     (QueryParam'
                                        '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
                                      :> Get '[JSON] TeamMemberList)
                                   :<|> (Named
                                           "unchecked-get-team-member"
                                           (Capture "uid" UserId
                                            :> (CanThrow 'TeamMemberNotFound
                                                :> Get '[JSON] TeamMember))
                                         :<|> (Named
                                                 "can-user-join-team"
                                                 ("check"
                                                  :> (CanThrow
                                                        'TooManyTeamMembersOnTeamWithLegalhold
                                                      :> MultiVerb
                                                           'GET
                                                           '[JSON]
                                                           '[RespondEmpty 200 "User can join"]
                                                           ()))
                                               :<|> Named
                                                      "unchecked-update-team-member"
                                                      (CanThrow 'AccessDenied
                                                       :> (CanThrow 'InvalidPermissions
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow 'TeamMemberNotFound
                                                                   :> (CanThrow 'TooManyTeamAdmins
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     NewTeamMember
                                                                                   :> MultiVerb
                                                                                        'PUT
                                                                                        '[JSON]
                                                                                        '[RespondEmpty
                                                                                            200 ""]
                                                                                        ())))))))))))))
                        :<|> (Named
                                "user-is-team-owner"
                                ("is-team-owner"
                                 :> (Capture "uid" UserId
                                     :> (CanThrow 'AccessDenied
                                         :> (CanThrow 'TeamMemberNotFound
                                             :> (CanThrow 'NotATeamMember
                                                 :> MultiVerb
                                                      'GET
                                                      '[JSON]
                                                      '[RespondEmpty 200 "User is team owner"]
                                                      ())))))
                              :<|> ("search-visibility"
                                    :> (Named
                                          "get-search-visibility-internal"
                                          (Get '[JSON] TeamSearchVisibilityView)
                                        :<|> Named
                                               "set-search-visibility-internal"
                                               (CanThrow 'TeamSearchVisibilityNotEnabled
                                                :> (CanThrow ('MissingPermission 'Nothing)
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> (ReqBody
                                                                  '[JSON] TeamSearchVisibilityView
                                                                :> MultiVerb
                                                                     'PUT
                                                                     '[JSON]
                                                                     '[RespondEmpty 204 "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
        "create-binding-team"
        (ZUser
         :> (ReqBody '[JSON] BindingNewTeam
             :> MultiVerb
                  'PUT
                  '[JSON]
                  '[WithHeaders
                      '[Header "Location" TeamId] TeamId (RespondEmpty 201 "OK")]
                  TeamId))
      :<|> (Named
              "delete-binding-team"
              (CanThrow 'NoBindingTeam
               :> (CanThrow 'NotAOneMemberTeam
                   :> (CanThrow 'DeleteQueueFull
                       :> (CanThrow 'TeamNotFound
                           :> (QueryFlag "force"
                               :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 202 "OK"] ())))))
            :<|> (Named
                    "get-team-name"
                    ("name" :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
                  :<|> (Named
                          "update-team-status"
                          ("status"
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow 'InvalidTeamStatusUpdate
                                   :> (ReqBody '[JSON] TeamStatusUpdate
                                       :> MultiVerb 'PUT '[JSON] '[RespondEmpty 200 "OK"] ()))))
                        :<|> (("members"
                               :> (Named
                                     "unchecked-add-team-member"
                                     (CanThrow 'TooManyTeamMembers
                                      :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                          :> (CanThrow 'TooManyTeamAdmins
                                              :> (ReqBody '[JSON] NewTeamMember
                                                  :> MultiVerb
                                                       'POST '[JSON] '[RespondEmpty 200 "OK"] ()))))
                                   :<|> (Named
                                           "unchecked-get-team-members"
                                           (QueryParam'
                                              '[Strict]
                                              "maxResults"
                                              (Range 1 HardTruncationLimit Int32)
                                            :> Get '[JSON] TeamMemberList)
                                         :<|> (Named
                                                 "unchecked-get-team-member"
                                                 (Capture "uid" UserId
                                                  :> (CanThrow 'TeamMemberNotFound
                                                      :> Get '[JSON] TeamMember))
                                               :<|> (Named
                                                       "can-user-join-team"
                                                       ("check"
                                                        :> (CanThrow
                                                              'TooManyTeamMembersOnTeamWithLegalhold
                                                            :> MultiVerb
                                                                 'GET
                                                                 '[JSON]
                                                                 '[RespondEmpty 200 "User can join"]
                                                                 ()))
                                                     :<|> Named
                                                            "unchecked-update-team-member"
                                                            (CanThrow 'AccessDenied
                                                             :> (CanThrow 'InvalidPermissions
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow
                                                                           'TeamMemberNotFound
                                                                         :> (CanThrow
                                                                               'TooManyTeamAdmins
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           NewTeamMember
                                                                                         :> MultiVerb
                                                                                              'PUT
                                                                                              '[JSON]
                                                                                              '[RespondEmpty
                                                                                                  200
                                                                                                  ""]
                                                                                              ())))))))))))))
                              :<|> (Named
                                      "user-is-team-owner"
                                      ("is-team-owner"
                                       :> (Capture "uid" UserId
                                           :> (CanThrow 'AccessDenied
                                               :> (CanThrow 'TeamMemberNotFound
                                                   :> (CanThrow 'NotATeamMember
                                                       :> MultiVerb
                                                            'GET
                                                            '[JSON]
                                                            '[RespondEmpty 200 "User is team owner"]
                                                            ())))))
                                    :<|> ("search-visibility"
                                          :> (Named
                                                "get-search-visibility-internal"
                                                (Get '[JSON] TeamSearchVisibilityView)
                                              :<|> Named
                                                     "set-search-visibility-internal"
                                                     (CanThrow 'TeamSearchVisibilityNotEnabled
                                                      :> (CanThrow ('MissingPermission 'Nothing)
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> (ReqBody
                                                                        '[JSON]
                                                                        TeamSearchVisibilityView
                                                                      :> MultiVerb
                                                                           'PUT
                                                                           '[JSON]
                                                                           '[RespondEmpty 204 "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]
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-binding-team" (TeamId
-> Bool
-> Sem
     '[ErrorS 'NoBindingTeam, Error (Tagged 'NotAOneMemberTeam ()),
       Error (Tagged 'DeleteQueueFull ()),
       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]
     ()
forall (r :: EffectRow).
(Member (ErrorS 'NoBindingTeam) r,
 Member (Error (Tagged 'TeamNotFound ())) r,
 Member (Error (Tagged 'NotAOneMemberTeam ())) r,
 Member (Error (Tagged 'DeleteQueueFull ())) r,
 Member (Queue DeleteItem) r, Member TeamStore r) =>
TeamId -> Bool -> Sem r ()
Teams.internalDeleteBindingTeam TeamId
tid)
        API
  (Named
     "delete-binding-team"
     (CanThrow 'NoBindingTeam
      :> (CanThrow 'NotAOneMemberTeam
          :> (CanThrow 'DeleteQueueFull
              :> (CanThrow 'TeamNotFound
                  :> (QueryFlag "force"
                      :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 202 "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
        "get-team-name"
        ("name" :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
      :<|> (Named
              "update-team-status"
              ("status"
               :> (CanThrow 'TeamNotFound
                   :> (CanThrow 'InvalidTeamStatusUpdate
                       :> (ReqBody '[JSON] TeamStatusUpdate
                           :> MultiVerb 'PUT '[JSON] '[RespondEmpty 200 "OK"] ()))))
            :<|> (("members"
                   :> (Named
                         "unchecked-add-team-member"
                         (CanThrow 'TooManyTeamMembers
                          :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                              :> (CanThrow 'TooManyTeamAdmins
                                  :> (ReqBody '[JSON] NewTeamMember
                                      :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))))
                       :<|> (Named
                               "unchecked-get-team-members"
                               (QueryParam'
                                  '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
                                :> Get '[JSON] TeamMemberList)
                             :<|> (Named
                                     "unchecked-get-team-member"
                                     (Capture "uid" UserId
                                      :> (CanThrow 'TeamMemberNotFound :> Get '[JSON] TeamMember))
                                   :<|> (Named
                                           "can-user-join-team"
                                           ("check"
                                            :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                                :> MultiVerb
                                                     'GET
                                                     '[JSON]
                                                     '[RespondEmpty 200 "User can join"]
                                                     ()))
                                         :<|> Named
                                                "unchecked-update-team-member"
                                                (CanThrow 'AccessDenied
                                                 :> (CanThrow 'InvalidPermissions
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow 'TeamMemberNotFound
                                                             :> (CanThrow 'TooManyTeamAdmins
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (ReqBody
                                                                               '[JSON] NewTeamMember
                                                                             :> MultiVerb
                                                                                  'PUT
                                                                                  '[JSON]
                                                                                  '[RespondEmpty
                                                                                      200 ""]
                                                                                  ())))))))))))))
                  :<|> (Named
                          "user-is-team-owner"
                          ("is-team-owner"
                           :> (Capture "uid" UserId
                               :> (CanThrow 'AccessDenied
                                   :> (CanThrow 'TeamMemberNotFound
                                       :> (CanThrow 'NotATeamMember
                                           :> MultiVerb
                                                'GET
                                                '[JSON]
                                                '[RespondEmpty 200 "User is team owner"]
                                                ())))))
                        :<|> ("search-visibility"
                              :> (Named
                                    "get-search-visibility-internal"
                                    (Get '[JSON] TeamSearchVisibilityView)
                                  :<|> Named
                                         "set-search-visibility-internal"
                                         (CanThrow 'TeamSearchVisibilityNotEnabled
                                          :> (CanThrow ('MissingPermission 'Nothing)
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> (ReqBody '[JSON] TeamSearchVisibilityView
                                                          :> MultiVerb
                                                               'PUT
                                                               '[JSON]
                                                               '[RespondEmpty 204 "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-binding-team"
        (CanThrow 'NoBindingTeam
         :> (CanThrow 'NotAOneMemberTeam
             :> (CanThrow 'DeleteQueueFull
                 :> (CanThrow 'TeamNotFound
                     :> (QueryFlag "force"
                         :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 202 "OK"] ())))))
      :<|> (Named
              "get-team-name"
              ("name" :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
            :<|> (Named
                    "update-team-status"
                    ("status"
                     :> (CanThrow 'TeamNotFound
                         :> (CanThrow 'InvalidTeamStatusUpdate
                             :> (ReqBody '[JSON] TeamStatusUpdate
                                 :> MultiVerb 'PUT '[JSON] '[RespondEmpty 200 "OK"] ()))))
                  :<|> (("members"
                         :> (Named
                               "unchecked-add-team-member"
                               (CanThrow 'TooManyTeamMembers
                                :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                    :> (CanThrow 'TooManyTeamAdmins
                                        :> (ReqBody '[JSON] NewTeamMember
                                            :> MultiVerb
                                                 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))))
                             :<|> (Named
                                     "unchecked-get-team-members"
                                     (QueryParam'
                                        '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
                                      :> Get '[JSON] TeamMemberList)
                                   :<|> (Named
                                           "unchecked-get-team-member"
                                           (Capture "uid" UserId
                                            :> (CanThrow 'TeamMemberNotFound
                                                :> Get '[JSON] TeamMember))
                                         :<|> (Named
                                                 "can-user-join-team"
                                                 ("check"
                                                  :> (CanThrow
                                                        'TooManyTeamMembersOnTeamWithLegalhold
                                                      :> MultiVerb
                                                           'GET
                                                           '[JSON]
                                                           '[RespondEmpty 200 "User can join"]
                                                           ()))
                                               :<|> Named
                                                      "unchecked-update-team-member"
                                                      (CanThrow 'AccessDenied
                                                       :> (CanThrow 'InvalidPermissions
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow 'TeamMemberNotFound
                                                                   :> (CanThrow 'TooManyTeamAdmins
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     NewTeamMember
                                                                                   :> MultiVerb
                                                                                        'PUT
                                                                                        '[JSON]
                                                                                        '[RespondEmpty
                                                                                            200 ""]
                                                                                        ())))))))))))))
                        :<|> (Named
                                "user-is-team-owner"
                                ("is-team-owner"
                                 :> (Capture "uid" UserId
                                     :> (CanThrow 'AccessDenied
                                         :> (CanThrow 'TeamMemberNotFound
                                             :> (CanThrow 'NotATeamMember
                                                 :> MultiVerb
                                                      'GET
                                                      '[JSON]
                                                      '[RespondEmpty 200 "User is team owner"]
                                                      ())))))
                              :<|> ("search-visibility"
                                    :> (Named
                                          "get-search-visibility-internal"
                                          (Get '[JSON] TeamSearchVisibilityView)
                                        :<|> Named
                                               "set-search-visibility-internal"
                                               (CanThrow 'TeamSearchVisibilityNotEnabled
                                                :> (CanThrow ('MissingPermission 'Nothing)
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> (ReqBody
                                                                  '[JSON] TeamSearchVisibilityView
                                                                :> MultiVerb
                                                                     'PUT
                                                                     '[JSON]
                                                                     '[RespondEmpty 204 "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]
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-team-name" (TeamId
-> Sem
     '[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]
     TeamName
forall (r :: EffectRow).
(Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r) =>
TeamId -> Sem r TeamName
Teams.getTeamNameInternalH TeamId
tid)
        API
  (Named
     "get-team-name"
     ("name" :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName)))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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-team-status"
        ("status"
         :> (CanThrow 'TeamNotFound
             :> (CanThrow 'InvalidTeamStatusUpdate
                 :> (ReqBody '[JSON] TeamStatusUpdate
                     :> MultiVerb 'PUT '[JSON] '[RespondEmpty 200 "OK"] ()))))
      :<|> (("members"
             :> (Named
                   "unchecked-add-team-member"
                   (CanThrow 'TooManyTeamMembers
                    :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                        :> (CanThrow 'TooManyTeamAdmins
                            :> (ReqBody '[JSON] NewTeamMember
                                :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))))
                 :<|> (Named
                         "unchecked-get-team-members"
                         (QueryParam'
                            '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
                          :> Get '[JSON] TeamMemberList)
                       :<|> (Named
                               "unchecked-get-team-member"
                               (Capture "uid" UserId
                                :> (CanThrow 'TeamMemberNotFound :> Get '[JSON] TeamMember))
                             :<|> (Named
                                     "can-user-join-team"
                                     ("check"
                                      :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                          :> MultiVerb
                                               'GET '[JSON] '[RespondEmpty 200 "User can join"] ()))
                                   :<|> Named
                                          "unchecked-update-team-member"
                                          (CanThrow 'AccessDenied
                                           :> (CanThrow 'InvalidPermissions
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow 'TeamMemberNotFound
                                                       :> (CanThrow 'TooManyTeamAdmins
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (ReqBody '[JSON] NewTeamMember
                                                                       :> MultiVerb
                                                                            'PUT
                                                                            '[JSON]
                                                                            '[RespondEmpty 200 ""]
                                                                            ())))))))))))))
            :<|> (Named
                    "user-is-team-owner"
                    ("is-team-owner"
                     :> (Capture "uid" UserId
                         :> (CanThrow 'AccessDenied
                             :> (CanThrow 'TeamMemberNotFound
                                 :> (CanThrow 'NotATeamMember
                                     :> MultiVerb
                                          'GET
                                          '[JSON]
                                          '[RespondEmpty 200 "User is team owner"]
                                          ())))))
                  :<|> ("search-visibility"
                        :> (Named
                              "get-search-visibility-internal"
                              (Get '[JSON] TeamSearchVisibilityView)
                            :<|> Named
                                   "set-search-visibility-internal"
                                   (CanThrow 'TeamSearchVisibilityNotEnabled
                                    :> (CanThrow ('MissingPermission 'Nothing)
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> (ReqBody '[JSON] TeamSearchVisibilityView
                                                    :> MultiVerb
                                                         'PUT
                                                         '[JSON]
                                                         '[RespondEmpty 204 "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
        "get-team-name"
        ("name" :> (CanThrow 'TeamNotFound :> Get '[JSON] TeamName))
      :<|> (Named
              "update-team-status"
              ("status"
               :> (CanThrow 'TeamNotFound
                   :> (CanThrow 'InvalidTeamStatusUpdate
                       :> (ReqBody '[JSON] TeamStatusUpdate
                           :> MultiVerb 'PUT '[JSON] '[RespondEmpty 200 "OK"] ()))))
            :<|> (("members"
                   :> (Named
                         "unchecked-add-team-member"
                         (CanThrow 'TooManyTeamMembers
                          :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                              :> (CanThrow 'TooManyTeamAdmins
                                  :> (ReqBody '[JSON] NewTeamMember
                                      :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))))
                       :<|> (Named
                               "unchecked-get-team-members"
                               (QueryParam'
                                  '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
                                :> Get '[JSON] TeamMemberList)
                             :<|> (Named
                                     "unchecked-get-team-member"
                                     (Capture "uid" UserId
                                      :> (CanThrow 'TeamMemberNotFound :> Get '[JSON] TeamMember))
                                   :<|> (Named
                                           "can-user-join-team"
                                           ("check"
                                            :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                                :> MultiVerb
                                                     'GET
                                                     '[JSON]
                                                     '[RespondEmpty 200 "User can join"]
                                                     ()))
                                         :<|> Named
                                                "unchecked-update-team-member"
                                                (CanThrow 'AccessDenied
                                                 :> (CanThrow 'InvalidPermissions
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow 'TeamMemberNotFound
                                                             :> (CanThrow 'TooManyTeamAdmins
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (ReqBody
                                                                               '[JSON] NewTeamMember
                                                                             :> MultiVerb
                                                                                  'PUT
                                                                                  '[JSON]
                                                                                  '[RespondEmpty
                                                                                      200 ""]
                                                                                  ())))))))))))))
                  :<|> (Named
                          "user-is-team-owner"
                          ("is-team-owner"
                           :> (Capture "uid" UserId
                               :> (CanThrow 'AccessDenied
                                   :> (CanThrow 'TeamMemberNotFound
                                       :> (CanThrow 'NotATeamMember
                                           :> MultiVerb
                                                'GET
                                                '[JSON]
                                                '[RespondEmpty 200 "User is team owner"]
                                                ())))))
                        :<|> ("search-visibility"
                              :> (Named
                                    "get-search-visibility-internal"
                                    (Get '[JSON] TeamSearchVisibilityView)
                                  :<|> Named
                                         "set-search-visibility-internal"
                                         (CanThrow 'TeamSearchVisibilityNotEnabled
                                          :> (CanThrow ('MissingPermission 'Nothing)
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> (ReqBody '[JSON] TeamSearchVisibilityView
                                                          :> MultiVerb
                                                               'PUT
                                                               '[JSON]
                                                               '[RespondEmpty 204 "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]
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-team-status" (TeamId
-> TeamStatusUpdate
-> Sem
     '[Error (Tagged 'TeamNotFound ()),
       Error (Tagged 'InvalidTeamStatusUpdate ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 BrigAccess r,
 Member (Error (Tagged 'InvalidTeamStatusUpdate ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r,
 Member (Input UTCTime) r, Member TeamStore r) =>
TeamId -> TeamStatusUpdate -> Sem r ()
Teams.updateTeamStatus TeamId
tid)
        API
  (Named
     "update-team-status"
     ("status"
      :> (CanThrow 'TeamNotFound
          :> (CanThrow 'InvalidTeamStatusUpdate
              :> (ReqBody '[JSON] TeamStatusUpdate
                  :> MultiVerb 'PUT '[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
     (("members"
       :> (Named
             "unchecked-add-team-member"
             (CanThrow 'TooManyTeamMembers
              :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                  :> (CanThrow 'TooManyTeamAdmins
                      :> (ReqBody '[JSON] NewTeamMember
                          :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))))
           :<|> (Named
                   "unchecked-get-team-members"
                   (QueryParam'
                      '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
                    :> Get '[JSON] TeamMemberList)
                 :<|> (Named
                         "unchecked-get-team-member"
                         (Capture "uid" UserId
                          :> (CanThrow 'TeamMemberNotFound :> Get '[JSON] TeamMember))
                       :<|> (Named
                               "can-user-join-team"
                               ("check"
                                :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                    :> MultiVerb
                                         'GET '[JSON] '[RespondEmpty 200 "User can join"] ()))
                             :<|> Named
                                    "unchecked-update-team-member"
                                    (CanThrow 'AccessDenied
                                     :> (CanThrow 'InvalidPermissions
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow 'TeamMemberNotFound
                                                 :> (CanThrow 'TooManyTeamAdmins
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (ReqBody '[JSON] NewTeamMember
                                                                 :> MultiVerb
                                                                      'PUT
                                                                      '[JSON]
                                                                      '[RespondEmpty 200 ""]
                                                                      ())))))))))))))
      :<|> (Named
              "user-is-team-owner"
              ("is-team-owner"
               :> (Capture "uid" UserId
                   :> (CanThrow 'AccessDenied
                       :> (CanThrow 'TeamMemberNotFound
                           :> (CanThrow 'NotATeamMember
                               :> MultiVerb
                                    'GET '[JSON] '[RespondEmpty 200 "User is team owner"] ())))))
            :<|> ("search-visibility"
                  :> (Named
                        "get-search-visibility-internal"
                        (Get '[JSON] TeamSearchVisibilityView)
                      :<|> Named
                             "set-search-visibility-internal"
                             (CanThrow 'TeamSearchVisibilityNotEnabled
                              :> (CanThrow ('MissingPermission 'Nothing)
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> (ReqBody '[JSON] TeamSearchVisibilityView
                                              :> MultiVerb
                                                   'PUT '[JSON] '[RespondEmpty 204 "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
        "update-team-status"
        ("status"
         :> (CanThrow 'TeamNotFound
             :> (CanThrow 'InvalidTeamStatusUpdate
                 :> (ReqBody '[JSON] TeamStatusUpdate
                     :> MultiVerb 'PUT '[JSON] '[RespondEmpty 200 "OK"] ()))))
      :<|> (("members"
             :> (Named
                   "unchecked-add-team-member"
                   (CanThrow 'TooManyTeamMembers
                    :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                        :> (CanThrow 'TooManyTeamAdmins
                            :> (ReqBody '[JSON] NewTeamMember
                                :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))))
                 :<|> (Named
                         "unchecked-get-team-members"
                         (QueryParam'
                            '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
                          :> Get '[JSON] TeamMemberList)
                       :<|> (Named
                               "unchecked-get-team-member"
                               (Capture "uid" UserId
                                :> (CanThrow 'TeamMemberNotFound :> Get '[JSON] TeamMember))
                             :<|> (Named
                                     "can-user-join-team"
                                     ("check"
                                      :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                          :> MultiVerb
                                               'GET '[JSON] '[RespondEmpty 200 "User can join"] ()))
                                   :<|> Named
                                          "unchecked-update-team-member"
                                          (CanThrow 'AccessDenied
                                           :> (CanThrow 'InvalidPermissions
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow 'TeamMemberNotFound
                                                       :> (CanThrow 'TooManyTeamAdmins
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (ReqBody '[JSON] NewTeamMember
                                                                       :> MultiVerb
                                                                            'PUT
                                                                            '[JSON]
                                                                            '[RespondEmpty 200 ""]
                                                                            ())))))))))))))
            :<|> (Named
                    "user-is-team-owner"
                    ("is-team-owner"
                     :> (Capture "uid" UserId
                         :> (CanThrow 'AccessDenied
                             :> (CanThrow 'TeamMemberNotFound
                                 :> (CanThrow 'NotATeamMember
                                     :> MultiVerb
                                          'GET
                                          '[JSON]
                                          '[RespondEmpty 200 "User is team owner"]
                                          ())))))
                  :<|> ("search-visibility"
                        :> (Named
                              "get-search-visibility-internal"
                              (Get '[JSON] TeamSearchVisibilityView)
                            :<|> Named
                                   "set-search-visibility-internal"
                                   (CanThrow 'TeamSearchVisibilityNotEnabled
                                    :> (CanThrow ('MissingPermission 'Nothing)
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> (ReqBody '[JSON] TeamSearchVisibilityView
                                                    :> MultiVerb
                                                         'PUT
                                                         '[JSON]
                                                         '[RespondEmpty 204 "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]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> API
  (Named
     "unchecked-add-team-member"
     (CanThrow 'TooManyTeamMembers
      :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
          :> (CanThrow 'TooManyTeamAdmins
              :> (ReqBody '[JSON] NewTeamMember
                  :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))))
   :<|> (Named
           "unchecked-get-team-members"
           (QueryParam'
              '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
            :> Get '[JSON] TeamMemberList)
         :<|> (Named
                 "unchecked-get-team-member"
                 (Capture "uid" UserId
                  :> (CanThrow 'TeamMemberNotFound :> Get '[JSON] TeamMember))
               :<|> (Named
                       "can-user-join-team"
                       ("check"
                        :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                            :> MultiVerb 'GET '[JSON] '[RespondEmpty 200 "User can join"] ()))
                     :<|> Named
                            "unchecked-update-team-member"
                            (CanThrow 'AccessDenied
                             :> (CanThrow 'InvalidPermissions
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow 'TeamMemberNotFound
                                         :> (CanThrow 'TooManyTeamAdmins
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (ReqBody '[JSON] NewTeamMember
                                                         :> MultiVerb
                                                              'PUT
                                                              '[JSON]
                                                              '[RespondEmpty 200 ""]
                                                              ()))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     ("members"
      :> (Named
            "unchecked-add-team-member"
            (CanThrow 'TooManyTeamMembers
             :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                 :> (CanThrow 'TooManyTeamAdmins
                     :> (ReqBody '[JSON] NewTeamMember
                         :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))))
          :<|> (Named
                  "unchecked-get-team-members"
                  (QueryParam'
                     '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
                   :> Get '[JSON] TeamMemberList)
                :<|> (Named
                        "unchecked-get-team-member"
                        (Capture "uid" UserId
                         :> (CanThrow 'TeamMemberNotFound :> Get '[JSON] TeamMember))
                      :<|> (Named
                              "can-user-join-team"
                              ("check"
                               :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                   :> MultiVerb
                                        'GET '[JSON] '[RespondEmpty 200 "User can join"] ()))
                            :<|> Named
                                   "unchecked-update-team-member"
                                   (CanThrow 'AccessDenied
                                    :> (CanThrow 'InvalidPermissions
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow 'TeamMemberNotFound
                                                :> (CanThrow 'TooManyTeamAdmins
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (ReqBody '[JSON] NewTeamMember
                                                                :> MultiVerb
                                                                     'PUT
                                                                     '[JSON]
                                                                     '[RespondEmpty 200 ""]
                                                                     ())))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 {k} (seg :: k) inner (r :: EffectRow).
(ServerT (seg :> inner) (Sem r) ~ ServerT inner (Sem r)) =>
API inner r -> API (seg :> inner) r
hoistAPISegment
          ( 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 @"unchecked-add-team-member" (TeamId
-> NewTeamMember
-> Sem
     '[Error (Tagged 'TooManyTeamMembers ()),
       Error (Tagged 'TooManyTeamMembersOnTeamWithLegalhold ()),
       Error (Tagged 'TooManyTeamAdmins ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 BrigAccess r, Member NotificationSubsystem r,
 Member (Error (Tagged 'TooManyTeamMembers ())) r,
 Member (Error (Tagged 'TooManyTeamAdmins ())) r,
 Member
   (Error (Tagged 'TooManyTeamMembersOnTeamWithLegalhold ())) r,
 Member (Input Opts) r, Member (Input UTCTime) r,
 Member LegalHoldStore r, Member (Logger (Msg -> Msg)) r,
 Member TeamFeatureStore r, Member TeamNotificationStore r,
 Member TeamStore r) =>
TeamId -> NewTeamMember -> Sem r ()
Teams.uncheckedAddTeamMember TeamId
tid)
              API
  (Named
     "unchecked-add-team-member"
     (CanThrow 'TooManyTeamMembers
      :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
          :> (CanThrow 'TooManyTeamAdmins
              :> (ReqBody '[JSON] NewTeamMember
                  :> MultiVerb 'POST '[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
        "unchecked-get-team-members"
        (QueryParam'
           '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
         :> Get '[JSON] TeamMemberList)
      :<|> (Named
              "unchecked-get-team-member"
              (Capture "uid" UserId
               :> (CanThrow 'TeamMemberNotFound :> Get '[JSON] TeamMember))
            :<|> (Named
                    "can-user-join-team"
                    ("check"
                     :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                         :> MultiVerb 'GET '[JSON] '[RespondEmpty 200 "User can join"] ()))
                  :<|> Named
                         "unchecked-update-team-member"
                         (CanThrow 'AccessDenied
                          :> (CanThrow 'InvalidPermissions
                              :> (CanThrow 'TeamNotFound
                                  :> (CanThrow 'TeamMemberNotFound
                                      :> (CanThrow 'TooManyTeamAdmins
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (ReqBody '[JSON] NewTeamMember
                                                      :> MultiVerb
                                                           'PUT
                                                           '[JSON]
                                                           '[RespondEmpty 200 ""]
                                                           ())))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "unchecked-add-team-member"
        (CanThrow 'TooManyTeamMembers
         :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
             :> (CanThrow 'TooManyTeamAdmins
                 :> (ReqBody '[JSON] NewTeamMember
                     :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))))
      :<|> (Named
              "unchecked-get-team-members"
              (QueryParam'
                 '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
               :> Get '[JSON] TeamMemberList)
            :<|> (Named
                    "unchecked-get-team-member"
                    (Capture "uid" UserId
                     :> (CanThrow 'TeamMemberNotFound :> Get '[JSON] TeamMember))
                  :<|> (Named
                          "can-user-join-team"
                          ("check"
                           :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                               :> MultiVerb 'GET '[JSON] '[RespondEmpty 200 "User can join"] ()))
                        :<|> Named
                               "unchecked-update-team-member"
                               (CanThrow 'AccessDenied
                                :> (CanThrow 'InvalidPermissions
                                    :> (CanThrow 'TeamNotFound
                                        :> (CanThrow 'TeamMemberNotFound
                                            :> (CanThrow 'TooManyTeamAdmins
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (ReqBody '[JSON] NewTeamMember
                                                            :> MultiVerb
                                                                 'PUT
                                                                 '[JSON]
                                                                 '[RespondEmpty 200 ""]
                                                                 ()))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"unchecked-get-team-members" (TeamId
-> Maybe (Range 1 HardTruncationLimit 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]
     TeamMemberList
forall (r :: EffectRow).
Member TeamStore r =>
TeamId
-> Maybe (Range 1 HardTruncationLimit Int32)
-> Sem r TeamMemberList
Teams.uncheckedGetTeamMembersH TeamId
tid)
              API
  (Named
     "unchecked-get-team-members"
     (QueryParam'
        '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
      :> Get '[JSON] TeamMemberList))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "unchecked-get-team-member"
        (Capture "uid" UserId
         :> (CanThrow 'TeamMemberNotFound :> Get '[JSON] TeamMember))
      :<|> (Named
              "can-user-join-team"
              ("check"
               :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                   :> MultiVerb 'GET '[JSON] '[RespondEmpty 200 "User can join"] ()))
            :<|> Named
                   "unchecked-update-team-member"
                   (CanThrow 'AccessDenied
                    :> (CanThrow 'InvalidPermissions
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow 'TeamMemberNotFound
                                :> (CanThrow 'TooManyTeamAdmins
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (ReqBody '[JSON] NewTeamMember
                                                :> MultiVerb
                                                     'PUT
                                                     '[JSON]
                                                     '[RespondEmpty 200 ""]
                                                     ()))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "unchecked-get-team-members"
        (QueryParam'
           '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
         :> Get '[JSON] TeamMemberList)
      :<|> (Named
              "unchecked-get-team-member"
              (Capture "uid" UserId
               :> (CanThrow 'TeamMemberNotFound :> Get '[JSON] TeamMember))
            :<|> (Named
                    "can-user-join-team"
                    ("check"
                     :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                         :> MultiVerb 'GET '[JSON] '[RespondEmpty 200 "User can join"] ()))
                  :<|> Named
                         "unchecked-update-team-member"
                         (CanThrow 'AccessDenied
                          :> (CanThrow 'InvalidPermissions
                              :> (CanThrow 'TeamNotFound
                                  :> (CanThrow 'TeamMemberNotFound
                                      :> (CanThrow 'TooManyTeamAdmins
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (ReqBody '[JSON] NewTeamMember
                                                      :> MultiVerb
                                                           'PUT
                                                           '[JSON]
                                                           '[RespondEmpty 200 ""]
                                                           ())))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"unchecked-get-team-member" (TeamId
-> UserId
-> Sem
     '[ErrorS 'TeamMemberNotFound, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     TeamMember
forall (r :: EffectRow).
(Member (ErrorS 'TeamMemberNotFound) r, Member TeamStore r) =>
TeamId -> UserId -> Sem r TeamMember
Teams.uncheckedGetTeamMember TeamId
tid)
              API
  (Named
     "unchecked-get-team-member"
     (Capture "uid" UserId
      :> (CanThrow 'TeamMemberNotFound :> Get '[JSON] TeamMember)))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "can-user-join-team"
        ("check"
         :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
             :> MultiVerb 'GET '[JSON] '[RespondEmpty 200 "User can join"] ()))
      :<|> Named
             "unchecked-update-team-member"
             (CanThrow 'AccessDenied
              :> (CanThrow 'InvalidPermissions
                  :> (CanThrow 'TeamNotFound
                      :> (CanThrow 'TeamMemberNotFound
                          :> (CanThrow 'TooManyTeamAdmins
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (ReqBody '[JSON] NewTeamMember
                                          :> MultiVerb
                                               'PUT '[JSON] '[RespondEmpty 200 ""] ())))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "unchecked-get-team-member"
        (Capture "uid" UserId
         :> (CanThrow 'TeamMemberNotFound :> Get '[JSON] TeamMember))
      :<|> (Named
              "can-user-join-team"
              ("check"
               :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                   :> MultiVerb 'GET '[JSON] '[RespondEmpty 200 "User can join"] ()))
            :<|> Named
                   "unchecked-update-team-member"
                   (CanThrow 'AccessDenied
                    :> (CanThrow 'InvalidPermissions
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow 'TeamMemberNotFound
                                :> (CanThrow 'TooManyTeamAdmins
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (ReqBody '[JSON] NewTeamMember
                                                :> MultiVerb
                                                     'PUT
                                                     '[JSON]
                                                     '[RespondEmpty 200 ""]
                                                     ()))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"can-user-join-team" (TeamId
-> Sem
     '[Error (Tagged 'TooManyTeamMembersOnTeamWithLegalhold ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 BrigAccess r, Member LegalHoldStore r, Member TeamStore r,
 Member TeamFeatureStore r,
 Member
   (Error (Tagged 'TooManyTeamMembersOnTeamWithLegalhold ())) r) =>
TeamId -> Sem r ()
Teams.canUserJoinTeam TeamId
tid)
              API
  (Named
     "can-user-join-team"
     ("check"
      :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
          :> MultiVerb 'GET '[JSON] '[RespondEmpty 200 "User can join"] ())))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "unchecked-update-team-member"
        (CanThrow 'AccessDenied
         :> (CanThrow 'InvalidPermissions
             :> (CanThrow 'TeamNotFound
                 :> (CanThrow 'TeamMemberNotFound
                     :> (CanThrow 'TooManyTeamAdmins
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow ('MissingPermission 'Nothing)
                                 :> (ReqBody '[JSON] NewTeamMember
                                     :> MultiVerb 'PUT '[JSON] '[RespondEmpty 200 ""] ())))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "can-user-join-team"
        ("check"
         :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
             :> MultiVerb 'GET '[JSON] '[RespondEmpty 200 "User can join"] ()))
      :<|> Named
             "unchecked-update-team-member"
             (CanThrow 'AccessDenied
              :> (CanThrow 'InvalidPermissions
                  :> (CanThrow 'TeamNotFound
                      :> (CanThrow 'TeamMemberNotFound
                          :> (CanThrow 'TooManyTeamAdmins
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (ReqBody '[JSON] NewTeamMember
                                          :> MultiVerb
                                               'PUT '[JSON] '[RespondEmpty 200 ""] ())))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"unchecked-update-team-member" (Maybe (QualifiedWithTag 'QLocal UserId)
-> Maybe ConnId
-> TeamId
-> NewTeamMember
-> Sem
     '[Error (Tagged 'AccessDenied ()),
       Error (Tagged 'InvalidPermissions ()),
       Error (Tagged 'TeamNotFound ()), ErrorS 'TeamMemberNotFound,
       Error (Tagged 'TooManyTeamAdmins ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged ('MissingPermission 'Nothing) ()), BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 BrigAccess r, Member (Error (Tagged 'TeamNotFound ())) r,
 Member (ErrorS 'TeamMemberNotFound) r,
 Member (Error (Tagged 'TooManyTeamAdmins ())) r,
 Member NotificationSubsystem r, Member (Input UTCTime) r,
 Member (Logger (Msg -> Msg)) r, Member TeamStore r) =>
Maybe (QualifiedWithTag 'QLocal UserId)
-> Maybe ConnId -> TeamId -> NewTeamMember -> Sem r ()
Teams.uncheckedUpdateTeamMember Maybe (QualifiedWithTag 'QLocal UserId)
forall a. Maybe a
Nothing Maybe ConnId
forall a. Maybe a
Nothing TeamId
tid)
          )
        API
  ("members"
   :> (Named
         "unchecked-add-team-member"
         (CanThrow 'TooManyTeamMembers
          :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
              :> (CanThrow 'TooManyTeamAdmins
                  :> (ReqBody '[JSON] NewTeamMember
                      :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))))
       :<|> (Named
               "unchecked-get-team-members"
               (QueryParam'
                  '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
                :> Get '[JSON] TeamMemberList)
             :<|> (Named
                     "unchecked-get-team-member"
                     (Capture "uid" UserId
                      :> (CanThrow 'TeamMemberNotFound :> Get '[JSON] TeamMember))
                   :<|> (Named
                           "can-user-join-team"
                           ("check"
                            :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                :> MultiVerb 'GET '[JSON] '[RespondEmpty 200 "User can join"] ()))
                         :<|> Named
                                "unchecked-update-team-member"
                                (CanThrow 'AccessDenied
                                 :> (CanThrow 'InvalidPermissions
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow 'TeamMemberNotFound
                                             :> (CanThrow 'TooManyTeamAdmins
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow ('MissingPermission 'Nothing)
                                                         :> (ReqBody '[JSON] NewTeamMember
                                                             :> MultiVerb
                                                                  'PUT
                                                                  '[JSON]
                                                                  '[RespondEmpty 200 ""]
                                                                  ())))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "user-is-team-owner"
        ("is-team-owner"
         :> (Capture "uid" UserId
             :> (CanThrow 'AccessDenied
                 :> (CanThrow 'TeamMemberNotFound
                     :> (CanThrow 'NotATeamMember
                         :> MultiVerb
                              'GET '[JSON] '[RespondEmpty 200 "User is team owner"] ())))))
      :<|> ("search-visibility"
            :> (Named
                  "get-search-visibility-internal"
                  (Get '[JSON] TeamSearchVisibilityView)
                :<|> Named
                       "set-search-visibility-internal"
                       (CanThrow 'TeamSearchVisibilityNotEnabled
                        :> (CanThrow ('MissingPermission 'Nothing)
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> (ReqBody '[JSON] TeamSearchVisibilityView
                                        :> MultiVerb
                                             'PUT '[JSON] '[RespondEmpty 204 "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
     (("members"
       :> (Named
             "unchecked-add-team-member"
             (CanThrow 'TooManyTeamMembers
              :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                  :> (CanThrow 'TooManyTeamAdmins
                      :> (ReqBody '[JSON] NewTeamMember
                          :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))))
           :<|> (Named
                   "unchecked-get-team-members"
                   (QueryParam'
                      '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
                    :> Get '[JSON] TeamMemberList)
                 :<|> (Named
                         "unchecked-get-team-member"
                         (Capture "uid" UserId
                          :> (CanThrow 'TeamMemberNotFound :> Get '[JSON] TeamMember))
                       :<|> (Named
                               "can-user-join-team"
                               ("check"
                                :> (CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                                    :> MultiVerb
                                         'GET '[JSON] '[RespondEmpty 200 "User can join"] ()))
                             :<|> Named
                                    "unchecked-update-team-member"
                                    (CanThrow 'AccessDenied
                                     :> (CanThrow 'InvalidPermissions
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow 'TeamMemberNotFound
                                                 :> (CanThrow 'TooManyTeamAdmins
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (ReqBody '[JSON] NewTeamMember
                                                                 :> MultiVerb
                                                                      'PUT
                                                                      '[JSON]
                                                                      '[RespondEmpty 200 ""]
                                                                      ())))))))))))))
      :<|> (Named
              "user-is-team-owner"
              ("is-team-owner"
               :> (Capture "uid" UserId
                   :> (CanThrow 'AccessDenied
                       :> (CanThrow 'TeamMemberNotFound
                           :> (CanThrow 'NotATeamMember
                               :> MultiVerb
                                    'GET '[JSON] '[RespondEmpty 200 "User is team owner"] ())))))
            :<|> ("search-visibility"
                  :> (Named
                        "get-search-visibility-internal"
                        (Get '[JSON] TeamSearchVisibilityView)
                      :<|> Named
                             "set-search-visibility-internal"
                             (CanThrow 'TeamSearchVisibilityNotEnabled
                              :> (CanThrow ('MissingPermission 'Nothing)
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> (ReqBody '[JSON] TeamSearchVisibilityView
                                              :> MultiVerb
                                                   'PUT '[JSON] '[RespondEmpty 204 "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]
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 @"user-is-team-owner" (TeamId
-> UserId
-> Sem
     '[Error (Tagged 'AccessDenied ()), ErrorS 'TeamMemberNotFound,
       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]
     ()
forall (r :: EffectRow).
(Member (ErrorS 'TeamMemberNotFound) r,
 Member (Error (Tagged 'AccessDenied ())) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Input (Local ())) r, Member TeamStore r) =>
TeamId -> UserId -> Sem r ()
Teams.userIsTeamOwner TeamId
tid)
        API
  (Named
     "user-is-team-owner"
     ("is-team-owner"
      :> (Capture "uid" UserId
          :> (CanThrow 'AccessDenied
              :> (CanThrow 'TeamMemberNotFound
                  :> (CanThrow 'NotATeamMember
                      :> MultiVerb
                           'GET '[JSON] '[RespondEmpty 200 "User is team owner"] ()))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     ("search-visibility"
      :> (Named
            "get-search-visibility-internal"
            (Get '[JSON] TeamSearchVisibilityView)
          :<|> Named
                 "set-search-visibility-internal"
                 (CanThrow 'TeamSearchVisibilityNotEnabled
                  :> (CanThrow ('MissingPermission 'Nothing)
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> (ReqBody '[JSON] TeamSearchVisibilityView
                                  :> MultiVerb 'PUT '[JSON] '[RespondEmpty 204 "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
        "user-is-team-owner"
        ("is-team-owner"
         :> (Capture "uid" UserId
             :> (CanThrow 'AccessDenied
                 :> (CanThrow 'TeamMemberNotFound
                     :> (CanThrow 'NotATeamMember
                         :> MultiVerb
                              'GET '[JSON] '[RespondEmpty 200 "User is team owner"] ())))))
      :<|> ("search-visibility"
            :> (Named
                  "get-search-visibility-internal"
                  (Get '[JSON] TeamSearchVisibilityView)
                :<|> Named
                       "set-search-visibility-internal"
                       (CanThrow 'TeamSearchVisibilityNotEnabled
                        :> (CanThrow ('MissingPermission 'Nothing)
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> (ReqBody '[JSON] TeamSearchVisibilityView
                                        :> MultiVerb
                                             'PUT '[JSON] '[RespondEmpty 204 "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]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> API
  (Named
     "get-search-visibility-internal"
     (Get '[JSON] TeamSearchVisibilityView)
   :<|> Named
          "set-search-visibility-internal"
          (CanThrow 'TeamSearchVisibilityNotEnabled
           :> (CanThrow ('MissingPermission 'Nothing)
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow 'TeamNotFound
                       :> (ReqBody '[JSON] TeamSearchVisibilityView
                           :> MultiVerb 'PUT '[JSON] '[RespondEmpty 204 "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
     ("search-visibility"
      :> (Named
            "get-search-visibility-internal"
            (Get '[JSON] TeamSearchVisibilityView)
          :<|> Named
                 "set-search-visibility-internal"
                 (CanThrow 'TeamSearchVisibilityNotEnabled
                  :> (CanThrow ('MissingPermission 'Nothing)
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> (ReqBody '[JSON] TeamSearchVisibilityView
                                  :> MultiVerb 'PUT '[JSON] '[RespondEmpty 204 "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]
forall {k} (seg :: k) inner (r :: EffectRow).
(ServerT (seg :> inner) (Sem r) ~ ServerT inner (Sem r)) =>
API inner r -> API (seg :> inner) r
hoistAPISegment
          ( 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-search-visibility-internal" (TeamId
-> 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]
     TeamSearchVisibilityView
forall (r :: EffectRow).
Member SearchVisibilityStore r =>
TeamId -> Sem r TeamSearchVisibilityView
Teams.getSearchVisibilityInternal TeamId
tid)
              API
  (Named
     "get-search-visibility-internal"
     (Get '[JSON] TeamSearchVisibilityView))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "set-search-visibility-internal"
        (CanThrow 'TeamSearchVisibilityNotEnabled
         :> (CanThrow ('MissingPermission 'Nothing)
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> (ReqBody '[JSON] TeamSearchVisibilityView
                         :> MultiVerb 'PUT '[JSON] '[RespondEmpty 204 "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
        "get-search-visibility-internal"
        (Get '[JSON] TeamSearchVisibilityView)
      :<|> Named
             "set-search-visibility-internal"
             (CanThrow 'TeamSearchVisibilityNotEnabled
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> (ReqBody '[JSON] TeamSearchVisibilityView
                              :> MultiVerb 'PUT '[JSON] '[RespondEmpty 204 "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]
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 @"set-search-visibility-internal" ((TeamId
 -> Sem
      '[ErrorS 'TeamSearchVisibilityNotEnabled,
        Error (Tagged ('MissingPermission 'Nothing) ()),
        Error (Tagged 'NotATeamMember ()), 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]
      Bool)
-> TeamId
-> TeamSearchVisibilityView
-> Sem
     '[ErrorS 'TeamSearchVisibilityNotEnabled,
       Error (Tagged ('MissingPermission 'Nothing) ()),
       Error (Tagged 'NotATeamMember ()), 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]
     ()
forall (r :: EffectRow).
(Member (ErrorS 'TeamSearchVisibilityNotEnabled) r,
 Member SearchVisibilityStore r) =>
(TeamId -> Sem r Bool)
-> TeamId -> TeamSearchVisibilityView -> Sem r ()
Teams.setSearchVisibilityInternal (forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, Member (Input Opts) r,
 Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r,
 Member TeamFeatureStore r, ComputeFeatureConstraints cfg r) =>
TeamId -> Sem r Bool
featureEnabledForTeam @SearchVisibilityAvailableConfig) TeamId
tid)
          )

miscAPI :: API IMiscAPI GalleyEffects
miscAPI :: API IMiscAPI GalleyEffects
miscAPI =
  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-team-members" ServerT
  (CanThrow 'NonBindingTeam
   :> (CanThrow 'TeamNotFound
       :> ("users"
           :> (Capture "uid" UserId
               :> ("team" :> ("members" :> Get '[JSON] TeamMemberList))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (CanThrow 'NonBindingTeam
            :> (CanThrow 'TeamNotFound
                :> ("users"
                    :> (Capture "uid" UserId
                        :> ("team" :> ("members" :> Get '[JSON] TeamMemberList)))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (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
-> Sem
     '[Error (Tagged 'NonBindingTeam ()),
       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]
     TeamMemberList
forall (r :: EffectRow).
(Member (Error (Tagged 'TeamNotFound ())) r,
 Member (Error (Tagged 'NonBindingTeam ())) r,
 Member TeamStore r) =>
UserId -> Sem r TeamMemberList
Teams.getBindingTeamMembers
    API
  (Named
     "get-team-members"
     (CanThrow 'NonBindingTeam
      :> (CanThrow 'TeamNotFound
          :> ("users"
              :> (Capture "uid" UserId
                  :> ("team" :> ("members" :> Get '[JSON] TeamMemberList)))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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-team-id"
        (CanThrow 'NonBindingTeam
         :> (CanThrow 'TeamNotFound
             :> ("users"
                 :> (Capture "uid" UserId :> ("team" :> Get '[JSON] TeamId)))))
      :<|> (Named
              "test-get-clients"
              ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
            :<|> (Named
                    "test-add-client"
                    ("clients"
                     :> (ZUser
                         :> (Capture "cid" ClientId
                             :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
                  :<|> (Named
                          "test-delete-client"
                          ("clients"
                           :> (ZUser
                               :> (Capture "cid" ClientId
                                   :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
                        :<|> (Named
                                "add-service"
                                ("services"
                                 :> (ReqBody '[JSON] Service
                                     :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
                              :<|> (Named
                                      "delete-service"
                                      ("services"
                                       :> (ReqBody '[JSON] ServiceRef
                                           :> MultiVerb
                                                'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
                                    :<|> (Named
                                            "i-add-bot"
                                            (CanThrow ('ActionDenied 'AddConversationMember)
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (CanThrow 'TooManyMembers
                                                         :> ("bots"
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> (ReqBody '[JSON] AddBot
                                                                         :> Post
                                                                              '[JSON] Event))))))))
                                          :<|> (Named
                                                  "delete-bot"
                                                  (CanThrow 'ConvNotFound
                                                   :> (CanThrow
                                                         ('ActionDenied 'RemoveConversationMember)
                                                       :> ("bots"
                                                           :> (ZLocalUser
                                                               :> (ZOptConn
                                                                   :> (ReqBody '[JSON] RemoveBot
                                                                       :> MultiVerb
                                                                            'DELETE
                                                                            '[JSON]
                                                                            (UpdateResponses
                                                                               "Bot not found"
                                                                               "Bot deleted"
                                                                               Event)
                                                                            (UpdateResult
                                                                               Event)))))))
                                                :<|> (Named
                                                        "put-custom-backend"
                                                        ("custom-backend"
                                                         :> ("by-domain"
                                                             :> (Capture "domain" Domain
                                                                 :> (ReqBody '[JSON] CustomBackend
                                                                     :> MultiVerb
                                                                          'PUT
                                                                          '[JSON]
                                                                          '[RespondEmpty 201 "OK"]
                                                                          ()))))
                                                      :<|> Named
                                                             "delete-custom-backend"
                                                             ("custom-backend"
                                                              :> ("by-domain"
                                                                  :> (Capture "domain" Domain
                                                                      :> 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
        "get-team-members"
        (CanThrow 'NonBindingTeam
         :> (CanThrow 'TeamNotFound
             :> ("users"
                 :> (Capture "uid" UserId
                     :> ("team" :> ("members" :> Get '[JSON] TeamMemberList))))))
      :<|> (Named
              "get-team-id"
              (CanThrow 'NonBindingTeam
               :> (CanThrow 'TeamNotFound
                   :> ("users"
                       :> (Capture "uid" UserId :> ("team" :> Get '[JSON] TeamId)))))
            :<|> (Named
                    "test-get-clients"
                    ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
                  :<|> (Named
                          "test-add-client"
                          ("clients"
                           :> (ZUser
                               :> (Capture "cid" ClientId
                                   :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
                        :<|> (Named
                                "test-delete-client"
                                ("clients"
                                 :> (ZUser
                                     :> (Capture "cid" ClientId
                                         :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
                              :<|> (Named
                                      "add-service"
                                      ("services"
                                       :> (ReqBody '[JSON] Service
                                           :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
                                    :<|> (Named
                                            "delete-service"
                                            ("services"
                                             :> (ReqBody '[JSON] ServiceRef
                                                 :> MultiVerb
                                                      'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
                                          :<|> (Named
                                                  "i-add-bot"
                                                  (CanThrow ('ActionDenied 'AddConversationMember)
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'InvalidOperation
                                                           :> (CanThrow 'TooManyMembers
                                                               :> ("bots"
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> (ReqBody
                                                                                 '[JSON] AddBot
                                                                               :> Post
                                                                                    '[JSON]
                                                                                    Event))))))))
                                                :<|> (Named
                                                        "delete-bot"
                                                        (CanThrow 'ConvNotFound
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'RemoveConversationMember)
                                                             :> ("bots"
                                                                 :> (ZLocalUser
                                                                     :> (ZOptConn
                                                                         :> (ReqBody
                                                                               '[JSON] RemoveBot
                                                                             :> MultiVerb
                                                                                  'DELETE
                                                                                  '[JSON]
                                                                                  (UpdateResponses
                                                                                     "Bot not found"
                                                                                     "Bot deleted"
                                                                                     Event)
                                                                                  (UpdateResult
                                                                                     Event)))))))
                                                      :<|> (Named
                                                              "put-custom-backend"
                                                              ("custom-backend"
                                                               :> ("by-domain"
                                                                   :> (Capture "domain" Domain
                                                                       :> (ReqBody
                                                                             '[JSON] CustomBackend
                                                                           :> MultiVerb
                                                                                'PUT
                                                                                '[JSON]
                                                                                '[RespondEmpty
                                                                                    201 "OK"]
                                                                                ()))))
                                                            :<|> Named
                                                                   "delete-custom-backend"
                                                                   ("custom-backend"
                                                                    :> ("by-domain"
                                                                        :> (Capture "domain" Domain
                                                                            :> 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]
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-team-id" ServerT
  (CanThrow 'NonBindingTeam
   :> (CanThrow 'TeamNotFound
       :> ("users"
           :> (Capture "uid" UserId :> ("team" :> Get '[JSON] TeamId)))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (CanThrow 'NonBindingTeam
            :> (CanThrow 'TeamNotFound
                :> ("users"
                    :> (Capture "uid" UserId :> ("team" :> Get '[JSON] TeamId))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (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
-> Sem
     '[Error (Tagged 'NonBindingTeam ()),
       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]
     TeamId
forall (r :: EffectRow).
(Member (Error (Tagged 'TeamNotFound ())) r,
 Member (Error (Tagged 'NonBindingTeam ())) r,
 Member TeamStore r) =>
UserId -> Sem r TeamId
lookupBindingTeam
    API
  (Named
     "get-team-id"
     (CanThrow 'NonBindingTeam
      :> (CanThrow 'TeamNotFound
          :> ("users"
              :> (Capture "uid" UserId :> ("team" :> Get '[JSON] TeamId))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "test-get-clients"
        ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
      :<|> (Named
              "test-add-client"
              ("clients"
               :> (ZUser
                   :> (Capture "cid" ClientId
                       :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
            :<|> (Named
                    "test-delete-client"
                    ("clients"
                     :> (ZUser
                         :> (Capture "cid" ClientId
                             :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
                  :<|> (Named
                          "add-service"
                          ("services"
                           :> (ReqBody '[JSON] Service
                               :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
                        :<|> (Named
                                "delete-service"
                                ("services"
                                 :> (ReqBody '[JSON] ServiceRef
                                     :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
                              :<|> (Named
                                      "i-add-bot"
                                      (CanThrow ('ActionDenied 'AddConversationMember)
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'InvalidOperation
                                               :> (CanThrow 'TooManyMembers
                                                   :> ("bots"
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> (ReqBody '[JSON] AddBot
                                                                   :> Post '[JSON] Event))))))))
                                    :<|> (Named
                                            "delete-bot"
                                            (CanThrow 'ConvNotFound
                                             :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                                 :> ("bots"
                                                     :> (ZLocalUser
                                                         :> (ZOptConn
                                                             :> (ReqBody '[JSON] RemoveBot
                                                                 :> MultiVerb
                                                                      'DELETE
                                                                      '[JSON]
                                                                      (UpdateResponses
                                                                         "Bot not found"
                                                                         "Bot deleted"
                                                                         Event)
                                                                      (UpdateResult Event)))))))
                                          :<|> (Named
                                                  "put-custom-backend"
                                                  ("custom-backend"
                                                   :> ("by-domain"
                                                       :> (Capture "domain" Domain
                                                           :> (ReqBody '[JSON] CustomBackend
                                                               :> MultiVerb
                                                                    'PUT
                                                                    '[JSON]
                                                                    '[RespondEmpty 201 "OK"]
                                                                    ()))))
                                                :<|> Named
                                                       "delete-custom-backend"
                                                       ("custom-backend"
                                                        :> ("by-domain"
                                                            :> (Capture "domain" Domain
                                                                :> 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
        "get-team-id"
        (CanThrow 'NonBindingTeam
         :> (CanThrow 'TeamNotFound
             :> ("users"
                 :> (Capture "uid" UserId :> ("team" :> Get '[JSON] TeamId)))))
      :<|> (Named
              "test-get-clients"
              ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
            :<|> (Named
                    "test-add-client"
                    ("clients"
                     :> (ZUser
                         :> (Capture "cid" ClientId
                             :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
                  :<|> (Named
                          "test-delete-client"
                          ("clients"
                           :> (ZUser
                               :> (Capture "cid" ClientId
                                   :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
                        :<|> (Named
                                "add-service"
                                ("services"
                                 :> (ReqBody '[JSON] Service
                                     :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
                              :<|> (Named
                                      "delete-service"
                                      ("services"
                                       :> (ReqBody '[JSON] ServiceRef
                                           :> MultiVerb
                                                'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
                                    :<|> (Named
                                            "i-add-bot"
                                            (CanThrow ('ActionDenied 'AddConversationMember)
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (CanThrow 'TooManyMembers
                                                         :> ("bots"
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> (ReqBody '[JSON] AddBot
                                                                         :> Post
                                                                              '[JSON] Event))))))))
                                          :<|> (Named
                                                  "delete-bot"
                                                  (CanThrow 'ConvNotFound
                                                   :> (CanThrow
                                                         ('ActionDenied 'RemoveConversationMember)
                                                       :> ("bots"
                                                           :> (ZLocalUser
                                                               :> (ZOptConn
                                                                   :> (ReqBody '[JSON] RemoveBot
                                                                       :> MultiVerb
                                                                            'DELETE
                                                                            '[JSON]
                                                                            (UpdateResponses
                                                                               "Bot not found"
                                                                               "Bot deleted"
                                                                               Event)
                                                                            (UpdateResult
                                                                               Event)))))))
                                                :<|> (Named
                                                        "put-custom-backend"
                                                        ("custom-backend"
                                                         :> ("by-domain"
                                                             :> (Capture "domain" Domain
                                                                 :> (ReqBody '[JSON] CustomBackend
                                                                     :> MultiVerb
                                                                          'PUT
                                                                          '[JSON]
                                                                          '[RespondEmpty 201 "OK"]
                                                                          ()))))
                                                      :<|> Named
                                                             "delete-custom-backend"
                                                             ("custom-backend"
                                                              :> ("by-domain"
                                                                  :> (Capture "domain" Domain
                                                                      :> 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]
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 @"test-get-clients" ServerT
  ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
  (Sem
     (Append
        (DeclaredErrorEffects
           ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId]))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (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
-> 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]
     [ClientId]
forall (r :: EffectRow).
(Member BrigAccess r, Member ClientStore r) =>
UserId -> Sem r [ClientId]
Clients.getClients
    API
  (Named
     "test-get-clients"
     ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId]))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "test-add-client"
        ("clients"
         :> (ZUser
             :> (Capture "cid" ClientId
                 :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
      :<|> (Named
              "test-delete-client"
              ("clients"
               :> (ZUser
                   :> (Capture "cid" ClientId
                       :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
            :<|> (Named
                    "add-service"
                    ("services"
                     :> (ReqBody '[JSON] Service
                         :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
                  :<|> (Named
                          "delete-service"
                          ("services"
                           :> (ReqBody '[JSON] ServiceRef
                               :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
                        :<|> (Named
                                "i-add-bot"
                                (CanThrow ('ActionDenied 'AddConversationMember)
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'InvalidOperation
                                         :> (CanThrow 'TooManyMembers
                                             :> ("bots"
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> (ReqBody '[JSON] AddBot
                                                             :> Post '[JSON] Event))))))))
                              :<|> (Named
                                      "delete-bot"
                                      (CanThrow 'ConvNotFound
                                       :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                           :> ("bots"
                                               :> (ZLocalUser
                                                   :> (ZOptConn
                                                       :> (ReqBody '[JSON] RemoveBot
                                                           :> MultiVerb
                                                                'DELETE
                                                                '[JSON]
                                                                (UpdateResponses
                                                                   "Bot not found"
                                                                   "Bot deleted"
                                                                   Event)
                                                                (UpdateResult Event)))))))
                                    :<|> (Named
                                            "put-custom-backend"
                                            ("custom-backend"
                                             :> ("by-domain"
                                                 :> (Capture "domain" Domain
                                                     :> (ReqBody '[JSON] CustomBackend
                                                         :> MultiVerb
                                                              'PUT
                                                              '[JSON]
                                                              '[RespondEmpty 201 "OK"]
                                                              ()))))
                                          :<|> Named
                                                 "delete-custom-backend"
                                                 ("custom-backend"
                                                  :> ("by-domain"
                                                      :> (Capture "domain" Domain
                                                          :> 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
        "test-get-clients"
        ("test" :> ("clients" :> (ZUser :> Get '[JSON] [ClientId])))
      :<|> (Named
              "test-add-client"
              ("clients"
               :> (ZUser
                   :> (Capture "cid" ClientId
                       :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
            :<|> (Named
                    "test-delete-client"
                    ("clients"
                     :> (ZUser
                         :> (Capture "cid" ClientId
                             :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
                  :<|> (Named
                          "add-service"
                          ("services"
                           :> (ReqBody '[JSON] Service
                               :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
                        :<|> (Named
                                "delete-service"
                                ("services"
                                 :> (ReqBody '[JSON] ServiceRef
                                     :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
                              :<|> (Named
                                      "i-add-bot"
                                      (CanThrow ('ActionDenied 'AddConversationMember)
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'InvalidOperation
                                               :> (CanThrow 'TooManyMembers
                                                   :> ("bots"
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> (ReqBody '[JSON] AddBot
                                                                   :> Post '[JSON] Event))))))))
                                    :<|> (Named
                                            "delete-bot"
                                            (CanThrow 'ConvNotFound
                                             :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                                 :> ("bots"
                                                     :> (ZLocalUser
                                                         :> (ZOptConn
                                                             :> (ReqBody '[JSON] RemoveBot
                                                                 :> MultiVerb
                                                                      'DELETE
                                                                      '[JSON]
                                                                      (UpdateResponses
                                                                         "Bot not found"
                                                                         "Bot deleted"
                                                                         Event)
                                                                      (UpdateResult Event)))))))
                                          :<|> (Named
                                                  "put-custom-backend"
                                                  ("custom-backend"
                                                   :> ("by-domain"
                                                       :> (Capture "domain" Domain
                                                           :> (ReqBody '[JSON] CustomBackend
                                                               :> MultiVerb
                                                                    'PUT
                                                                    '[JSON]
                                                                    '[RespondEmpty 201 "OK"]
                                                                    ()))))
                                                :<|> Named
                                                       "delete-custom-backend"
                                                       ("custom-backend"
                                                        :> ("by-domain"
                                                            :> (Capture "domain" Domain
                                                                :> 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]
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 @"test-add-client" ServerT
  ("clients"
   :> (ZUser
       :> (Capture "cid" ClientId
           :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
  (Sem
     (Append
        (DeclaredErrorEffects
           ("clients"
            :> (ZUser
                :> (Capture "cid" ClientId
                    :> MultiVerb 'POST '[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]))
UserId
-> ClientId
-> 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]
     ()
forall (r :: EffectRow).
Member ClientStore r =>
UserId -> ClientId -> Sem r ()
createClient
    API
  (Named
     "test-add-client"
     ("clients"
      :> (ZUser
          :> (Capture "cid" ClientId
              :> MultiVerb 'POST '[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
        "test-delete-client"
        ("clients"
         :> (ZUser
             :> (Capture "cid" ClientId
                 :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
      :<|> (Named
              "add-service"
              ("services"
               :> (ReqBody '[JSON] Service
                   :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
            :<|> (Named
                    "delete-service"
                    ("services"
                     :> (ReqBody '[JSON] ServiceRef
                         :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
                  :<|> (Named
                          "i-add-bot"
                          (CanThrow ('ActionDenied 'AddConversationMember)
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'InvalidOperation
                                   :> (CanThrow 'TooManyMembers
                                       :> ("bots"
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> (ReqBody '[JSON] AddBot
                                                       :> Post '[JSON] Event))))))))
                        :<|> (Named
                                "delete-bot"
                                (CanThrow 'ConvNotFound
                                 :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                     :> ("bots"
                                         :> (ZLocalUser
                                             :> (ZOptConn
                                                 :> (ReqBody '[JSON] RemoveBot
                                                     :> MultiVerb
                                                          'DELETE
                                                          '[JSON]
                                                          (UpdateResponses
                                                             "Bot not found" "Bot deleted" Event)
                                                          (UpdateResult Event)))))))
                              :<|> (Named
                                      "put-custom-backend"
                                      ("custom-backend"
                                       :> ("by-domain"
                                           :> (Capture "domain" Domain
                                               :> (ReqBody '[JSON] CustomBackend
                                                   :> MultiVerb
                                                        'PUT '[JSON] '[RespondEmpty 201 "OK"] ()))))
                                    :<|> Named
                                           "delete-custom-backend"
                                           ("custom-backend"
                                            :> ("by-domain"
                                                :> (Capture "domain" Domain
                                                    :> 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
        "test-add-client"
        ("clients"
         :> (ZUser
             :> (Capture "cid" ClientId
                 :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ())))
      :<|> (Named
              "test-delete-client"
              ("clients"
               :> (ZUser
                   :> (Capture "cid" ClientId
                       :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
            :<|> (Named
                    "add-service"
                    ("services"
                     :> (ReqBody '[JSON] Service
                         :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
                  :<|> (Named
                          "delete-service"
                          ("services"
                           :> (ReqBody '[JSON] ServiceRef
                               :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
                        :<|> (Named
                                "i-add-bot"
                                (CanThrow ('ActionDenied 'AddConversationMember)
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'InvalidOperation
                                         :> (CanThrow 'TooManyMembers
                                             :> ("bots"
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> (ReqBody '[JSON] AddBot
                                                             :> Post '[JSON] Event))))))))
                              :<|> (Named
                                      "delete-bot"
                                      (CanThrow 'ConvNotFound
                                       :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                           :> ("bots"
                                               :> (ZLocalUser
                                                   :> (ZOptConn
                                                       :> (ReqBody '[JSON] RemoveBot
                                                           :> MultiVerb
                                                                'DELETE
                                                                '[JSON]
                                                                (UpdateResponses
                                                                   "Bot not found"
                                                                   "Bot deleted"
                                                                   Event)
                                                                (UpdateResult Event)))))))
                                    :<|> (Named
                                            "put-custom-backend"
                                            ("custom-backend"
                                             :> ("by-domain"
                                                 :> (Capture "domain" Domain
                                                     :> (ReqBody '[JSON] CustomBackend
                                                         :> MultiVerb
                                                              'PUT
                                                              '[JSON]
                                                              '[RespondEmpty 201 "OK"]
                                                              ()))))
                                          :<|> Named
                                                 "delete-custom-backend"
                                                 ("custom-backend"
                                                  :> ("by-domain"
                                                      :> (Capture "domain" Domain
                                                          :> 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]
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 @"test-delete-client" ServerT
  ("clients"
   :> (ZUser
       :> (Capture "cid" ClientId
           :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
  (Sem
     (Append
        (DeclaredErrorEffects
           ("clients"
            :> (ZUser
                :> (Capture "cid" ClientId
                    :> 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]))
UserId
-> ClientId
-> 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]
     ()
forall p1 (r :: EffectRow).
(p1 ~ CassandraPaging, Member ClientStore r,
 Member ConversationStore r, Member (Error FederationError) r,
 Member ExternalAccess r, Member BackendNotificationQueueAccess r,
 Member NotificationSubsystem r, Member (Input Env) r,
 Member (Input (Local ())) r, Member (Input UTCTime) r,
 Member (ListItems p1 ConvId) r,
 Member (ListItems p1 (Remote ConvId)) r, Member MemberStore r,
 Member (Error InternalError) r, Member ProposalStore r,
 Member Random r, Member SubConversationStore r,
 Member (Logger (Msg -> Msg)) r) =>
UserId -> ClientId -> Sem r ()
Clients.rmClient
    API
  (Named
     "test-delete-client"
     ("clients"
      :> (ZUser
          :> (Capture "cid" ClientId
              :> 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
        "add-service"
        ("services"
         :> (ReqBody '[JSON] Service
             :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
      :<|> (Named
              "delete-service"
              ("services"
               :> (ReqBody '[JSON] ServiceRef
                   :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
            :<|> (Named
                    "i-add-bot"
                    (CanThrow ('ActionDenied 'AddConversationMember)
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'InvalidOperation
                             :> (CanThrow 'TooManyMembers
                                 :> ("bots"
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> (ReqBody '[JSON] AddBot
                                                 :> Post '[JSON] Event))))))))
                  :<|> (Named
                          "delete-bot"
                          (CanThrow 'ConvNotFound
                           :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                               :> ("bots"
                                   :> (ZLocalUser
                                       :> (ZOptConn
                                           :> (ReqBody '[JSON] RemoveBot
                                               :> MultiVerb
                                                    'DELETE
                                                    '[JSON]
                                                    (UpdateResponses
                                                       "Bot not found" "Bot deleted" Event)
                                                    (UpdateResult Event)))))))
                        :<|> (Named
                                "put-custom-backend"
                                ("custom-backend"
                                 :> ("by-domain"
                                     :> (Capture "domain" Domain
                                         :> (ReqBody '[JSON] CustomBackend
                                             :> MultiVerb
                                                  'PUT '[JSON] '[RespondEmpty 201 "OK"] ()))))
                              :<|> Named
                                     "delete-custom-backend"
                                     ("custom-backend"
                                      :> ("by-domain"
                                          :> (Capture "domain" Domain
                                              :> 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
        "test-delete-client"
        ("clients"
         :> (ZUser
             :> (Capture "cid" ClientId
                 :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
      :<|> (Named
              "add-service"
              ("services"
               :> (ReqBody '[JSON] Service
                   :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
            :<|> (Named
                    "delete-service"
                    ("services"
                     :> (ReqBody '[JSON] ServiceRef
                         :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
                  :<|> (Named
                          "i-add-bot"
                          (CanThrow ('ActionDenied 'AddConversationMember)
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'InvalidOperation
                                   :> (CanThrow 'TooManyMembers
                                       :> ("bots"
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> (ReqBody '[JSON] AddBot
                                                       :> Post '[JSON] Event))))))))
                        :<|> (Named
                                "delete-bot"
                                (CanThrow 'ConvNotFound
                                 :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                     :> ("bots"
                                         :> (ZLocalUser
                                             :> (ZOptConn
                                                 :> (ReqBody '[JSON] RemoveBot
                                                     :> MultiVerb
                                                          'DELETE
                                                          '[JSON]
                                                          (UpdateResponses
                                                             "Bot not found" "Bot deleted" Event)
                                                          (UpdateResult Event)))))))
                              :<|> (Named
                                      "put-custom-backend"
                                      ("custom-backend"
                                       :> ("by-domain"
                                           :> (Capture "domain" Domain
                                               :> (ReqBody '[JSON] CustomBackend
                                                   :> MultiVerb
                                                        'PUT '[JSON] '[RespondEmpty 201 "OK"] ()))))
                                    :<|> Named
                                           "delete-custom-backend"
                                           ("custom-backend"
                                            :> ("by-domain"
                                                :> (Capture "domain" Domain
                                                    :> 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]
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-service" ServerT
  ("services"
   :> (ReqBody '[JSON] Service
       :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
  (Sem
     (Append
        (DeclaredErrorEffects
           ("services"
            :> (ReqBody '[JSON] Service
                :> MultiVerb 'POST '[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]))
Service
-> 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]
     ()
forall (r :: EffectRow).
Member ServiceStore r =>
Service -> Sem r ()
createService
    API
  (Named
     "add-service"
     ("services"
      :> (ReqBody '[JSON] Service
          :> MultiVerb 'POST '[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-service"
        ("services"
         :> (ReqBody '[JSON] ServiceRef
             :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
      :<|> (Named
              "i-add-bot"
              (CanThrow ('ActionDenied 'AddConversationMember)
               :> (CanThrow 'ConvNotFound
                   :> (CanThrow 'InvalidOperation
                       :> (CanThrow 'TooManyMembers
                           :> ("bots"
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> (ReqBody '[JSON] AddBot :> Post '[JSON] Event))))))))
            :<|> (Named
                    "delete-bot"
                    (CanThrow 'ConvNotFound
                     :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                         :> ("bots"
                             :> (ZLocalUser
                                 :> (ZOptConn
                                     :> (ReqBody '[JSON] RemoveBot
                                         :> MultiVerb
                                              'DELETE
                                              '[JSON]
                                              (UpdateResponses "Bot not found" "Bot deleted" Event)
                                              (UpdateResult Event)))))))
                  :<|> (Named
                          "put-custom-backend"
                          ("custom-backend"
                           :> ("by-domain"
                               :> (Capture "domain" Domain
                                   :> (ReqBody '[JSON] CustomBackend
                                       :> MultiVerb 'PUT '[JSON] '[RespondEmpty 201 "OK"] ()))))
                        :<|> Named
                               "delete-custom-backend"
                               ("custom-backend"
                                :> ("by-domain"
                                    :> (Capture "domain" Domain
                                        :> 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
        "add-service"
        ("services"
         :> (ReqBody '[JSON] Service
             :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "OK"] ()))
      :<|> (Named
              "delete-service"
              ("services"
               :> (ReqBody '[JSON] ServiceRef
                   :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
            :<|> (Named
                    "i-add-bot"
                    (CanThrow ('ActionDenied 'AddConversationMember)
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'InvalidOperation
                             :> (CanThrow 'TooManyMembers
                                 :> ("bots"
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> (ReqBody '[JSON] AddBot
                                                 :> Post '[JSON] Event))))))))
                  :<|> (Named
                          "delete-bot"
                          (CanThrow 'ConvNotFound
                           :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                               :> ("bots"
                                   :> (ZLocalUser
                                       :> (ZOptConn
                                           :> (ReqBody '[JSON] RemoveBot
                                               :> MultiVerb
                                                    'DELETE
                                                    '[JSON]
                                                    (UpdateResponses
                                                       "Bot not found" "Bot deleted" Event)
                                                    (UpdateResult Event)))))))
                        :<|> (Named
                                "put-custom-backend"
                                ("custom-backend"
                                 :> ("by-domain"
                                     :> (Capture "domain" Domain
                                         :> (ReqBody '[JSON] CustomBackend
                                             :> MultiVerb
                                                  'PUT '[JSON] '[RespondEmpty 201 "OK"] ()))))
                              :<|> Named
                                     "delete-custom-backend"
                                     ("custom-backend"
                                      :> ("by-domain"
                                          :> (Capture "domain" Domain
                                              :> 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]
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-service" ServerT
  ("services"
   :> (ReqBody '[JSON] ServiceRef
       :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
  (Sem
     (Append
        (DeclaredErrorEffects
           ("services"
            :> (ReqBody '[JSON] ServiceRef
                :> 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]))
ServiceRef
-> 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]
     ()
forall (r :: EffectRow).
Member ServiceStore r =>
ServiceRef -> Sem r ()
deleteService
    API
  (Named
     "delete-service"
     ("services"
      :> (ReqBody '[JSON] ServiceRef
          :> 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
        "i-add-bot"
        (CanThrow ('ActionDenied 'AddConversationMember)
         :> (CanThrow 'ConvNotFound
             :> (CanThrow 'InvalidOperation
                 :> (CanThrow 'TooManyMembers
                     :> ("bots"
                         :> (ZLocalUser
                             :> (ZConn :> (ReqBody '[JSON] AddBot :> Post '[JSON] Event))))))))
      :<|> (Named
              "delete-bot"
              (CanThrow 'ConvNotFound
               :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                   :> ("bots"
                       :> (ZLocalUser
                           :> (ZOptConn
                               :> (ReqBody '[JSON] RemoveBot
                                   :> MultiVerb
                                        'DELETE
                                        '[JSON]
                                        (UpdateResponses "Bot not found" "Bot deleted" Event)
                                        (UpdateResult Event)))))))
            :<|> (Named
                    "put-custom-backend"
                    ("custom-backend"
                     :> ("by-domain"
                         :> (Capture "domain" Domain
                             :> (ReqBody '[JSON] CustomBackend
                                 :> MultiVerb 'PUT '[JSON] '[RespondEmpty 201 "OK"] ()))))
                  :<|> Named
                         "delete-custom-backend"
                         ("custom-backend"
                          :> ("by-domain"
                              :> (Capture "domain" Domain
                                  :> 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-service"
        ("services"
         :> (ReqBody '[JSON] ServiceRef
             :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ()))
      :<|> (Named
              "i-add-bot"
              (CanThrow ('ActionDenied 'AddConversationMember)
               :> (CanThrow 'ConvNotFound
                   :> (CanThrow 'InvalidOperation
                       :> (CanThrow 'TooManyMembers
                           :> ("bots"
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> (ReqBody '[JSON] AddBot :> Post '[JSON] Event))))))))
            :<|> (Named
                    "delete-bot"
                    (CanThrow 'ConvNotFound
                     :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                         :> ("bots"
                             :> (ZLocalUser
                                 :> (ZOptConn
                                     :> (ReqBody '[JSON] RemoveBot
                                         :> MultiVerb
                                              'DELETE
                                              '[JSON]
                                              (UpdateResponses "Bot not found" "Bot deleted" Event)
                                              (UpdateResult Event)))))))
                  :<|> (Named
                          "put-custom-backend"
                          ("custom-backend"
                           :> ("by-domain"
                               :> (Capture "domain" Domain
                                   :> (ReqBody '[JSON] CustomBackend
                                       :> MultiVerb 'PUT '[JSON] '[RespondEmpty 201 "OK"] ()))))
                        :<|> Named
                               "delete-custom-backend"
                               ("custom-backend"
                                :> ("by-domain"
                                    :> (Capture "domain" Domain
                                        :> 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]
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 @"i-add-bot" ServerT
  (CanThrow ('ActionDenied 'AddConversationMember)
   :> (CanThrow 'ConvNotFound
       :> (CanThrow 'InvalidOperation
           :> (CanThrow 'TooManyMembers
               :> ("bots"
                   :> (ZLocalUser
                       :> (ZConn :> (ReqBody '[JSON] AddBot :> Post '[JSON] Event))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (CanThrow ('ActionDenied 'AddConversationMember)
            :> (CanThrow 'ConvNotFound
                :> (CanThrow 'InvalidOperation
                    :> (CanThrow 'TooManyMembers
                        :> ("bots"
                            :> (ZLocalUser
                                :> (ZConn :> (ReqBody '[JSON] AddBot :> Post '[JSON] 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
-> AddBot
-> Sem
     '[Error (Tagged ('ActionDenied 'AddConversationMember) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       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]
     Event
forall (r :: EffectRow).
(Member ClientStore r, Member ConversationStore r,
 Member
   (Error (Tagged ('ActionDenied 'AddConversationMember) ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member (Error (Tagged 'TooManyMembers ())) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input Opts) r, Member (Input UTCTime) r,
 Member MemberStore r) =>
QualifiedWithTag 'QLocal UserId -> ConnId -> AddBot -> Sem r Event
Update.addBot
    API
  (Named
     "i-add-bot"
     (CanThrow ('ActionDenied 'AddConversationMember)
      :> (CanThrow 'ConvNotFound
          :> (CanThrow 'InvalidOperation
              :> (CanThrow 'TooManyMembers
                  :> ("bots"
                      :> (ZLocalUser
                          :> (ZConn :> (ReqBody '[JSON] AddBot :> Post '[JSON] 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-bot"
        (CanThrow 'ConvNotFound
         :> (CanThrow ('ActionDenied 'RemoveConversationMember)
             :> ("bots"
                 :> (ZLocalUser
                     :> (ZOptConn
                         :> (ReqBody '[JSON] RemoveBot
                             :> MultiVerb
                                  'DELETE
                                  '[JSON]
                                  (UpdateResponses "Bot not found" "Bot deleted" Event)
                                  (UpdateResult Event)))))))
      :<|> (Named
              "put-custom-backend"
              ("custom-backend"
               :> ("by-domain"
                   :> (Capture "domain" Domain
                       :> (ReqBody '[JSON] CustomBackend
                           :> MultiVerb 'PUT '[JSON] '[RespondEmpty 201 "OK"] ()))))
            :<|> Named
                   "delete-custom-backend"
                   ("custom-backend"
                    :> ("by-domain"
                        :> (Capture "domain" Domain
                            :> 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
        "i-add-bot"
        (CanThrow ('ActionDenied 'AddConversationMember)
         :> (CanThrow 'ConvNotFound
             :> (CanThrow 'InvalidOperation
                 :> (CanThrow 'TooManyMembers
                     :> ("bots"
                         :> (ZLocalUser
                             :> (ZConn :> (ReqBody '[JSON] AddBot :> Post '[JSON] Event))))))))
      :<|> (Named
              "delete-bot"
              (CanThrow 'ConvNotFound
               :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                   :> ("bots"
                       :> (ZLocalUser
                           :> (ZOptConn
                               :> (ReqBody '[JSON] RemoveBot
                                   :> MultiVerb
                                        'DELETE
                                        '[JSON]
                                        (UpdateResponses "Bot not found" "Bot deleted" Event)
                                        (UpdateResult Event)))))))
            :<|> (Named
                    "put-custom-backend"
                    ("custom-backend"
                     :> ("by-domain"
                         :> (Capture "domain" Domain
                             :> (ReqBody '[JSON] CustomBackend
                                 :> MultiVerb 'PUT '[JSON] '[RespondEmpty 201 "OK"] ()))))
                  :<|> Named
                         "delete-custom-backend"
                         ("custom-backend"
                          :> ("by-domain"
                              :> (Capture "domain" Domain
                                  :> 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]
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-bot" ServerT
  (CanThrow 'ConvNotFound
   :> (CanThrow ('ActionDenied 'RemoveConversationMember)
       :> ("bots"
           :> (ZLocalUser
               :> (ZOptConn
                   :> (ReqBody '[JSON] RemoveBot
                       :> MultiVerb
                            'DELETE
                            '[JSON]
                            (UpdateResponses "Bot not found" "Bot deleted" Event)
                            (UpdateResult Event)))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (CanThrow 'ConvNotFound
            :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                :> ("bots"
                    :> (ZLocalUser
                        :> (ZOptConn
                            :> (ReqBody '[JSON] RemoveBot
                                :> MultiVerb
                                     'DELETE
                                     '[JSON]
                                     (UpdateResponses "Bot not found" "Bot deleted" 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]))
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> RemoveBot
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 ClientStore r, Member ConversationStore r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input UTCTime) r, Member MemberStore r,
 Member
   (Error (Tagged ('ActionDenied 'RemoveConversationMember) ())) r) =>
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId -> RemoveBot -> Sem r (UpdateResult Event)
Update.rmBot
    API
  (Named
     "delete-bot"
     (CanThrow 'ConvNotFound
      :> (CanThrow ('ActionDenied 'RemoveConversationMember)
          :> ("bots"
              :> (ZLocalUser
                  :> (ZOptConn
                      :> (ReqBody '[JSON] RemoveBot
                          :> MultiVerb
                               'DELETE
                               '[JSON]
                               (UpdateResponses "Bot not found" "Bot deleted" 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
        "put-custom-backend"
        ("custom-backend"
         :> ("by-domain"
             :> (Capture "domain" Domain
                 :> (ReqBody '[JSON] CustomBackend
                     :> MultiVerb 'PUT '[JSON] '[RespondEmpty 201 "OK"] ()))))
      :<|> Named
             "delete-custom-backend"
             ("custom-backend"
              :> ("by-domain"
                  :> (Capture "domain" Domain
                      :> 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-bot"
        (CanThrow 'ConvNotFound
         :> (CanThrow ('ActionDenied 'RemoveConversationMember)
             :> ("bots"
                 :> (ZLocalUser
                     :> (ZOptConn
                         :> (ReqBody '[JSON] RemoveBot
                             :> MultiVerb
                                  'DELETE
                                  '[JSON]
                                  (UpdateResponses "Bot not found" "Bot deleted" Event)
                                  (UpdateResult Event)))))))
      :<|> (Named
              "put-custom-backend"
              ("custom-backend"
               :> ("by-domain"
                   :> (Capture "domain" Domain
                       :> (ReqBody '[JSON] CustomBackend
                           :> MultiVerb 'PUT '[JSON] '[RespondEmpty 201 "OK"] ()))))
            :<|> Named
                   "delete-custom-backend"
                   ("custom-backend"
                    :> ("by-domain"
                        :> (Capture "domain" Domain
                            :> 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]
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 @"put-custom-backend" ServerT
  ("custom-backend"
   :> ("by-domain"
       :> (Capture "domain" Domain
           :> (ReqBody '[JSON] CustomBackend
               :> MultiVerb 'PUT '[JSON] '[RespondEmpty 201 "OK"] ()))))
  (Sem
     (Append
        (DeclaredErrorEffects
           ("custom-backend"
            :> ("by-domain"
                :> (Capture "domain" Domain
                    :> (ReqBody '[JSON] CustomBackend
                        :> MultiVerb 'PUT '[JSON] '[RespondEmpty 201 "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]))
Domain
-> CustomBackend
-> 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]
     ()
forall (r :: EffectRow).
Member CustomBackendStore r =>
Domain -> CustomBackend -> Sem r ()
setCustomBackend
    API
  (Named
     "put-custom-backend"
     ("custom-backend"
      :> ("by-domain"
          :> (Capture "domain" Domain
              :> (ReqBody '[JSON] CustomBackend
                  :> MultiVerb 'PUT '[JSON] '[RespondEmpty 201 "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-custom-backend"
        ("custom-backend"
         :> ("by-domain"
             :> (Capture "domain" Domain
                 :> 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
        "put-custom-backend"
        ("custom-backend"
         :> ("by-domain"
             :> (Capture "domain" Domain
                 :> (ReqBody '[JSON] CustomBackend
                     :> MultiVerb 'PUT '[JSON] '[RespondEmpty 201 "OK"] ()))))
      :<|> Named
             "delete-custom-backend"
             ("custom-backend"
              :> ("by-domain"
                  :> (Capture "domain" Domain
                      :> 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]
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-custom-backend" ServerT
  ("custom-backend"
   :> ("by-domain"
       :> (Capture "domain" Domain
           :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "OK"] ())))
  (Sem
     (Append
        (DeclaredErrorEffects
           ("custom-backend"
            :> ("by-domain"
                :> (Capture "domain" Domain
                    :> 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]))
Domain
-> 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]
     ()
forall (r :: EffectRow).
Member CustomBackendStore r =>
Domain -> Sem r ()
deleteCustomBackend

featureAPI1Full ::
  forall cfg r.
  (_) =>
  API (IFeatureAPI1Full cfg) r
featureAPI1Full :: API (IFeatureAPI1Full cfg) r
featureAPI1Full =
  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 @'("iget", cfg) ServerT
  (Description (FeatureAPIDesc cfg)
   :> (Summary (AppendSymbol "Get config for " (FeatureSymbol cfg))
       :> (CanThrow ('MissingPermission 'Nothing)
           :> (CanThrow 'NotATeamMember
               :> (CanThrow 'TeamNotFound
                   :> ("teams"
                       :> (Capture "tid" TeamId
                           :> ("features"
                               :> (FeatureSymbol cfg :> Get '[JSON] (LockableFeature cfg))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Description (FeatureAPIDesc cfg)
            :> (Summary (AppendSymbol "Get config for " (FeatureSymbol cfg))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> ("teams"
                                :> (Capture "tid" TeamId
                                    :> ("features"
                                        :> (FeatureSymbol cfg
                                            :> Get '[JSON] (LockableFeature cfg)))))))))))
        r))
TeamId
-> Sem
     (Error (Tagged ('MissingPermission 'Nothing) ())
        : Error (Tagged 'NotATeamMember ())
        : Error (Tagged 'TeamNotFound ()) : r)
     (LockableFeature cfg)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 Member (Input Opts) r, Member (Error (Tagged 'TeamNotFound ())) r,
 Member TeamFeatureStore r, Member TeamStore r) =>
TeamId -> Sem r (LockableFeature cfg)
getFeatureInternal
    API
  (Named
     '("iget", cfg)
     (Description (FeatureAPIDesc cfg)
      :> (Summary (AppendSymbol "Get config for " (FeatureSymbol cfg))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol cfg
                                      :> Get '[JSON] (LockableFeature cfg)))))))))))
  r
-> API
     (Named
        '("iput", cfg)
        (Description (FeatureAPIDesc cfg)
         :> (Summary (AppendSymbol "Put config for " (FeatureSymbol cfg))
             :> (CanThrow ('MissingPermission 'Nothing)
                 :> (CanThrow 'NotATeamMember
                     :> (CanThrow 'TeamNotFound
                         :> (CanThrow TeamFeatureError
                             :> (CanThrowMany (FeatureErrors cfg)
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> (FeatureSymbol cfg
                                                 :> (ReqBody '[JSON] (Feature cfg)
                                                     :> Put
                                                          '[JSON] (LockableFeature cfg)))))))))))))
      :<|> Named
             '("ipatch", cfg)
             (Description (FeatureAPIDesc cfg)
              :> (Summary (AppendSymbol "Patch config for " (FeatureSymbol cfg))
                  :> (CanThrow ('MissingPermission 'Nothing)
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> (CanThrow TeamFeatureError
                                  :> (CanThrowMany (FeatureErrors cfg)
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> (FeatureSymbol cfg
                                                      :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                                          :> Patch
                                                               '[JSON]
                                                               (LockableFeature cfg))))))))))))))
     r
-> API (IFeatureAPI1Full cfg) r
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 @'("iput", cfg) ServerT
  (Description (FeatureAPIDesc cfg)
   :> (Summary (AppendSymbol "Put config for " (FeatureSymbol cfg))
       :> (CanThrow ('MissingPermission 'Nothing)
           :> (CanThrow 'NotATeamMember
               :> (CanThrow 'TeamNotFound
                   :> (CanThrow TeamFeatureError
                       :> (CanThrowMany (FeatureErrors cfg)
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> (FeatureSymbol cfg
                                           :> (ReqBody '[JSON] (Feature cfg)
                                               :> Put '[JSON] (LockableFeature cfg)))))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Description (FeatureAPIDesc cfg)
            :> (Summary (AppendSymbol "Put config for " (FeatureSymbol cfg))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors cfg)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol cfg
                                                    :> (ReqBody '[JSON] (Feature cfg)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature cfg))))))))))))))
        r))
TeamId
-> Feature cfg
-> Sem
     (Error (Tagged ('MissingPermission 'Nothing) ())
        : Error (Tagged 'NotATeamMember ())
        : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
        : Append
            (DeclaredErrorEffects
               (CanThrowMany (FeatureErrors cfg)
                :> ("teams"
                    :> (Capture "tid" TeamId
                        :> ("features"
                            :> (FeatureSymbol cfg
                                :> (ReqBody '[JSON] (Feature cfg)
                                    :> Put '[JSON] (LockableFeature cfg))))))))
            r)
     (LockableFeature cfg)
forall cfg (r :: EffectRow).
(SetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 SetFeatureForTeamConstraints cfg r,
 Member (Error (Tagged 'TeamNotFound ())) r,
 Member (Error TeamFeatureError) r, Member (Input Opts) r,
 Member TeamStore r, Member TeamFeatureStore r,
 Member (Logger (Msg -> Msg)) r, Member NotificationSubsystem r) =>
TeamId -> Feature cfg -> Sem r (LockableFeature cfg)
setFeatureInternal
    API
  (Named
     '("iput", cfg)
     (Description (FeatureAPIDesc cfg)
      :> (Summary (AppendSymbol "Put config for " (FeatureSymbol cfg))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> (CanThrow TeamFeatureError
                          :> (CanThrowMany (FeatureErrors cfg)
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> (FeatureSymbol cfg
                                              :> (ReqBody '[JSON] (Feature cfg)
                                                  :> Put '[JSON] (LockableFeature cfg))))))))))))))
  r
-> API
     (Named
        '("ipatch", cfg)
        (Description (FeatureAPIDesc cfg)
         :> (Summary (AppendSymbol "Patch config for " (FeatureSymbol cfg))
             :> (CanThrow ('MissingPermission 'Nothing)
                 :> (CanThrow 'NotATeamMember
                     :> (CanThrow 'TeamNotFound
                         :> (CanThrow TeamFeatureError
                             :> (CanThrowMany (FeatureErrors cfg)
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> (FeatureSymbol cfg
                                                 :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                                     :> Patch
                                                          '[JSON] (LockableFeature cfg))))))))))))))
     r
-> API
     (Named
        '("iput", cfg)
        (Description (FeatureAPIDesc cfg)
         :> (Summary (AppendSymbol "Put config for " (FeatureSymbol cfg))
             :> (CanThrow ('MissingPermission 'Nothing)
                 :> (CanThrow 'NotATeamMember
                     :> (CanThrow 'TeamNotFound
                         :> (CanThrow TeamFeatureError
                             :> (CanThrowMany (FeatureErrors cfg)
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> (FeatureSymbol cfg
                                                 :> (ReqBody '[JSON] (Feature cfg)
                                                     :> Put
                                                          '[JSON] (LockableFeature cfg)))))))))))))
      :<|> Named
             '("ipatch", cfg)
             (Description (FeatureAPIDesc cfg)
              :> (Summary (AppendSymbol "Patch config for " (FeatureSymbol cfg))
                  :> (CanThrow ('MissingPermission 'Nothing)
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> (CanThrow TeamFeatureError
                                  :> (CanThrowMany (FeatureErrors cfg)
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> (FeatureSymbol cfg
                                                      :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                                          :> Patch
                                                               '[JSON]
                                                               (LockableFeature cfg))))))))))))))
     r
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 @'("ipatch", cfg) ServerT
  (Description (FeatureAPIDesc cfg)
   :> (Summary (AppendSymbol "Patch config for " (FeatureSymbol cfg))
       :> (CanThrow ('MissingPermission 'Nothing)
           :> (CanThrow 'NotATeamMember
               :> (CanThrow 'TeamNotFound
                   :> (CanThrow TeamFeatureError
                       :> (CanThrowMany (FeatureErrors cfg)
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> (FeatureSymbol cfg
                                           :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                               :> Patch '[JSON] (LockableFeature cfg)))))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Description (FeatureAPIDesc cfg)
            :> (Summary (AppendSymbol "Patch config for " (FeatureSymbol cfg))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors cfg)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol cfg
                                                    :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                                        :> Patch
                                                             '[JSON]
                                                             (LockableFeature cfg))))))))))))))
        r))
TeamId
-> LockableFeaturePatch cfg
-> Sem
     (Error (Tagged ('MissingPermission 'Nothing) ())
        : Error (Tagged 'NotATeamMember ())
        : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
        : Append
            (DeclaredErrorEffects
               (CanThrowMany (FeatureErrors cfg)
                :> ("teams"
                    :> (Capture "tid" TeamId
                        :> ("features"
                            :> (FeatureSymbol cfg
                                :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                    :> Patch '[JSON] (LockableFeature cfg))))))))
            r)
     (LockableFeature cfg)
forall cfg (r :: EffectRow).
(SetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 SetFeatureForTeamConstraints cfg r,
 Member (Error (Tagged 'TeamNotFound ())) r, Member (Input Opts) r,
 Member TeamStore r, Member TeamFeatureStore r,
 Member (Logger (Msg -> Msg)) r, Member NotificationSubsystem r) =>
TeamId -> LockableFeaturePatch cfg -> Sem r (LockableFeature cfg)
patchFeatureInternal

featureAPI1Get ::
  forall cfg r.
  (_) =>
  API (IFeatureStatusGet cfg) r
featureAPI1Get :: API (IFeatureStatusGet cfg) r
featureAPI1Get = 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 @'("iget", cfg) ServerT
  (Description (FeatureAPIDesc cfg)
   :> (Summary (AppendSymbol "Get config for " (FeatureSymbol cfg))
       :> (CanThrow ('MissingPermission 'Nothing)
           :> (CanThrow 'NotATeamMember
               :> (CanThrow 'TeamNotFound
                   :> ("teams"
                       :> (Capture "tid" TeamId
                           :> ("features"
                               :> (FeatureSymbol cfg :> Get '[JSON] (LockableFeature cfg))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Description (FeatureAPIDesc cfg)
            :> (Summary (AppendSymbol "Get config for " (FeatureSymbol cfg))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> ("teams"
                                :> (Capture "tid" TeamId
                                    :> ("features"
                                        :> (FeatureSymbol cfg
                                            :> Get '[JSON] (LockableFeature cfg)))))))))))
        r))
TeamId
-> Sem
     (Error (Tagged ('MissingPermission 'Nothing) ())
        : Error (Tagged 'NotATeamMember ())
        : Error (Tagged 'TeamNotFound ()) : r)
     (LockableFeature cfg)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 Member (Input Opts) r, Member (Error (Tagged 'TeamNotFound ())) r,
 Member TeamFeatureStore r, Member TeamStore r) =>
TeamId -> Sem r (LockableFeature cfg)
getFeatureInternal

allFeaturesAPI :: API (IAllFeaturesAPI Features) GalleyEffects
allFeaturesAPI :: API (IAllFeaturesAPI Features) GalleyEffects
allFeaturesAPI =
  API
  (Named
     '("iget", LegalholdConfig)
     (Description ""
      :> (Summary "Get config for legalhold"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("legalhold"
                                      :> Get '[JSON] (LockableFeature LegalholdConfig))))))))))
   :<|> (Named
           '("iput", LegalholdConfig)
           (Description ""
            :> (Summary "Put config for legalhold"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany
                                      '[ 'ActionDenied 'RemoveConversationMember,
                                         'CannotEnableLegalHoldServiceLargeTeam,
                                         'LegalHoldNotEnabled, 'LegalHoldDisableUnimplemented,
                                         'LegalHoldServiceNotRegistered,
                                         'UserLegalHoldIllegalOperation,
                                         'LegalHoldCouldNotBlockConnections]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("legalhold"
                                                    :> (ReqBody '[JSON] (Feature LegalholdConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                LegalholdConfig)))))))))))))
         :<|> Named
                '("ipatch", LegalholdConfig)
                (Description ""
                 :> (Summary "Patch config for legalhold"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany
                                           '[ 'ActionDenied 'RemoveConversationMember,
                                              'CannotEnableLegalHoldServiceLargeTeam,
                                              'LegalHoldNotEnabled, 'LegalHoldDisableUnimplemented,
                                              'LegalHoldServiceNotRegistered,
                                              'UserLegalHoldIllegalOperation,
                                              'LegalHoldCouldNotBlockConnections]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("legalhold"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  LegalholdConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     LegalholdConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", LegalholdConfig)
     (Description (FeatureAPIDesc LegalholdConfig)
      :> (Summary
            (AppendSymbol "Get config for " (FeatureSymbol LegalholdConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol LegalholdConfig
                                      :> Get '[JSON] (LockableFeature LegalholdConfig))))))))))
   :<|> (Named
           '("iput", LegalholdConfig)
           (Description (FeatureAPIDesc LegalholdConfig)
            :> (Summary
                  (AppendSymbol "Put config for " (FeatureSymbol LegalholdConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors LegalholdConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol LegalholdConfig
                                                    :> (ReqBody '[JSON] (Feature LegalholdConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                LegalholdConfig)))))))))))))
         :<|> Named
                '("ipatch", LegalholdConfig)
                (Description (FeatureAPIDesc LegalholdConfig)
                 :> (Summary
                       (AppendSymbol "Patch config for " (FeatureSymbol LegalholdConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany (FeatureErrors LegalholdConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol LegalholdConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  LegalholdConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     LegalholdConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", LegalholdConfig)
     (Description ""
      :> (Summary "Get config for legalhold"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("legalhold"
                                      :> Get '[JSON] (LockableFeature LegalholdConfig))))))))))
   :<|> (Named
           '("iput", LegalholdConfig)
           (Description ""
            :> (Summary "Put config for legalhold"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany
                                      '[ 'ActionDenied 'RemoveConversationMember,
                                         'CannotEnableLegalHoldServiceLargeTeam,
                                         'LegalHoldNotEnabled, 'LegalHoldDisableUnimplemented,
                                         'LegalHoldServiceNotRegistered,
                                         'UserLegalHoldIllegalOperation,
                                         'LegalHoldCouldNotBlockConnections]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("legalhold"
                                                    :> (ReqBody '[JSON] (Feature LegalholdConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                LegalholdConfig)))))))))))))
         :<|> Named
                '("ipatch", LegalholdConfig)
                (Description ""
                 :> (Summary "Patch config for legalhold"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany
                                           '[ 'ActionDenied 'RemoveConversationMember,
                                              'CannotEnableLegalHoldServiceLargeTeam,
                                              'LegalHoldNotEnabled, 'LegalHoldDisableUnimplemented,
                                              'LegalHoldServiceNotRegistered,
                                              'UserLegalHoldIllegalOperation,
                                              'LegalHoldCouldNotBlockConnections]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("legalhold"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  LegalholdConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     LegalholdConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", SSOConfig)
         (Description ""
          :> (Summary "Get config for sso"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("sso" :> Get '[JSON] (LockableFeature SSOConfig))))))))))
       :<|> (Named
               '("iput", SSOConfig)
               (Description ""
                :> (Summary "Put config for sso"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("sso"
                                                        :> (ReqBody '[JSON] (Feature SSOConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SSOConfig)))))))))))))
             :<|> Named
                    '("ipatch", SSOConfig)
                    (Description ""
                     :> (Summary "Patch config for sso"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("sso"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch SSOConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SSOConfig)))))))))))))))
      :<|> ((Named
               '("iget", SearchVisibilityAvailableConfig)
               (Description ""
                :> (Summary "Get config for searchVisibility"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("searchVisibility"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        SearchVisibilityAvailableConfig))))))))))
             :<|> (Named
                     '("iput", SearchVisibilityAvailableConfig)
                     (Description ""
                      :> (Summary "Put config for searchVisibility"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("searchVisibility"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       SearchVisibilityAvailableConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          SearchVisibilityAvailableConfig)))))))))))))
                   :<|> Named
                          '("ipatch", SearchVisibilityAvailableConfig)
                          (Description ""
                           :> (Summary "Patch config for searchVisibility"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("searchVisibility"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            SearchVisibilityAvailableConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SearchVisibilityAvailableConfig)))))))))))))))
            :<|> ((Named
                     '("iget", SearchVisibilityInboundConfig)
                     (Description ""
                      :> (Summary "Get config for searchVisibilityInbound"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("searchVisibilityInbound"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              SearchVisibilityInboundConfig))))))))))
                   :<|> (Named
                           '("iput", SearchVisibilityInboundConfig)
                           (Description ""
                            :> (Summary "Put config for searchVisibilityInbound"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("searchVisibilityInbound"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             SearchVisibilityInboundConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                SearchVisibilityInboundConfig)))))))))))))
                         :<|> Named
                                '("ipatch", SearchVisibilityInboundConfig)
                                (Description ""
                                 :> (Summary "Patch config for searchVisibilityInbound"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("searchVisibilityInbound"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  SearchVisibilityInboundConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     SearchVisibilityInboundConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", ValidateSAMLEmailsConfig)
                           (Description ""
                            :> (Summary "Get config for validateSAMLemails"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("validateSAMLemails"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    ValidateSAMLEmailsConfig))))))))))
                         :<|> (Named
                                 '("iput", ValidateSAMLEmailsConfig)
                                 (Description ""
                                  :> (Summary "Put config for validateSAMLemails"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("validateSAMLemails"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   ValidateSAMLEmailsConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      ValidateSAMLEmailsConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", ValidateSAMLEmailsConfig)
                                      (Description ""
                                       :> (Summary "Patch config for validateSAMLemails"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("validateSAMLemails"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        ValidateSAMLEmailsConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           ValidateSAMLEmailsConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", DigitalSignaturesConfig)
                                 (Description ""
                                  :> (Summary "Get config for digitalSignatures"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("digitalSignatures"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          DigitalSignaturesConfig))))))))))
                               :<|> (Named
                                       '("iput", DigitalSignaturesConfig)
                                       (Description ""
                                        :> (Summary "Put config for digitalSignatures"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("digitalSignatures"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         DigitalSignaturesConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            DigitalSignaturesConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", DigitalSignaturesConfig)
                                            (Description ""
                                             :> (Summary "Patch config for digitalSignatures"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("digitalSignatures"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              DigitalSignaturesConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 DigitalSignaturesConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", AppLockConfig)
                                       (Description ""
                                        :> (Summary "Get config for appLock"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("appLock"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                AppLockConfig))))))))))
                                     :<|> (Named
                                             '("iput", AppLockConfig)
                                             (Description ""
                                              :> (Summary "Put config for appLock"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("appLock"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               AppLockConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  AppLockConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", AppLockConfig)
                                                  (Description ""
                                                   :> (Summary "Patch config for appLock"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("appLock"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    AppLockConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       AppLockConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", FileSharingConfig)
                                             (Description ""
                                              :> (Summary "Get config for fileSharing"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("fileSharing"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      FileSharingConfig))))))))))
                                           :<|> (Named
                                                   '("iput", FileSharingConfig)
                                                   (Description ""
                                                    :> (Summary "Put config for fileSharing"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("fileSharing"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     FileSharingConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        FileSharingConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", FileSharingConfig)
                                                        (Description ""
                                                         :> (Summary "Patch config for fileSharing"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("fileSharing"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          FileSharingConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             FileSharingConfig)))))))))))))))
                                          :<|> (Named
                                                  '("iget", ClassifiedDomainsConfig)
                                                  (Description ""
                                                   :> (Summary "Get config for classifiedDomains"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("classifiedDomains"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           ClassifiedDomainsConfig))))))))))
                                                :<|> ((Named
                                                         '("iget", ConferenceCallingConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Get config for conferenceCalling"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("conferenceCalling"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  ConferenceCallingConfig))))))))))
                                                       :<|> (Named
                                                               '("iput", ConferenceCallingConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for conferenceCalling"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("conferenceCalling"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 ConferenceCallingConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    ConferenceCallingConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch",
                                                                      ConferenceCallingConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for conferenceCalling"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("conferenceCalling"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      ConferenceCallingConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         ConferenceCallingConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget", SelfDeletingMessagesConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Get config for selfDeletingMessages"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("selfDeletingMessages"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        SelfDeletingMessagesConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput",
                                                                       SelfDeletingMessagesConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for selfDeletingMessages"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("selfDeletingMessages"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       SelfDeletingMessagesConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          SelfDeletingMessagesConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            SelfDeletingMessagesConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for selfDeletingMessages"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("selfDeletingMessages"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            SelfDeletingMessagesConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               SelfDeletingMessagesConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget", GuestLinksConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Get config for conversationGuestLinks"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("conversationGuestLinks"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              GuestLinksConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput",
                                                                             GuestLinksConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Put config for conversationGuestLinks"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("conversationGuestLinks"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             GuestLinksConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                GuestLinksConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  GuestLinksConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Patch config for conversationGuestLinks"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  GuestLinksConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     GuestLinksConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("iget",
                                                                             SndFactorPasswordChallengeConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Get config for sndFactorPasswordChallenge"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("sndFactorPasswordChallenge"
                                                                                                            :> Get
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    SndFactorPasswordChallengeConfig))))))))))
                                                                         :<|> (Named
                                                                                 '("iput",
                                                                                   SndFactorPasswordChallengeConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Put config for sndFactorPasswordChallenge"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("sndFactorPasswordChallenge"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (Feature
                                                                                                                                   SndFactorPasswordChallengeConfig)
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      SndFactorPasswordChallengeConfig)))))))))))))
                                                                               :<|> Named
                                                                                      '("ipatch",
                                                                                        SndFactorPasswordChallengeConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Patch config for sndFactorPasswordChallenge"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeaturePatch
                                                                                                                                        SndFactorPasswordChallengeConfig)
                                                                                                                                   :> Patch
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           SndFactorPasswordChallengeConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("iget",
                                                                                   MLSConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Get config for mls"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("mls"
                                                                                                                  :> Get
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          MLSConfig))))))))))
                                                                               :<|> (Named
                                                                                       '("iput",
                                                                                         MLSConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Put config for mls"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> (CanThrow
                                                                                                              TeamFeatureError
                                                                                                            :> (CanThrowMany
                                                                                                                  '[]
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mls"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      (Feature
                                                                                                                                         MLSConfig)
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            MLSConfig)))))))))))))
                                                                                     :<|> Named
                                                                                            '("ipatch",
                                                                                              MLSConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (Summary
                                                                                                   "Patch config for mls"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   TeamFeatureError
                                                                                                                 :> (CanThrowMany
                                                                                                                       '[]
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("mls"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeaturePatch
                                                                                                                                              MLSConfig)
                                                                                                                                         :> Patch
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 MLSConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("iget",
                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                        :> Get
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                     :<|> (Named
                                                                                             '("iput",
                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> (CanThrow
                                                                                                                    TeamFeatureError
                                                                                                                  :> (CanThrowMany
                                                                                                                        '[]
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                      :> (ReqBody
                                                                                                                                            '[JSON]
                                                                                                                                            (Feature
                                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                           :<|> Named
                                                                                                  '("ipatch",
                                                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (Summary
                                                                                                         "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         TeamFeatureError
                                                                                                                       :> (CanThrowMany
                                                                                                                             '[]
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                               :> Patch
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("iget",
                                                                                               OutlookCalIntegrationConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Get config for outlookCalIntegration"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> ("teams"
                                                                                                                  :> (Capture
                                                                                                                        "tid"
                                                                                                                        TeamId
                                                                                                                      :> ("features"
                                                                                                                          :> ("outlookCalIntegration"
                                                                                                                              :> Get
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      OutlookCalIntegrationConfig))))))))))
                                                                                           :<|> (Named
                                                                                                   '("iput",
                                                                                                     OutlookCalIntegrationConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (Summary
                                                                                                          "Put config for outlookCalIntegration"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> (CanThrow
                                                                                                                          TeamFeatureError
                                                                                                                        :> (CanThrowMany
                                                                                                                              '[]
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("outlookCalIntegration"
                                                                                                                                            :> (ReqBody
                                                                                                                                                  '[JSON]
                                                                                                                                                  (Feature
                                                                                                                                                     OutlookCalIntegrationConfig)
                                                                                                                                                :> Put
                                                                                                                                                     '[JSON]
                                                                                                                                                     (LockableFeature
                                                                                                                                                        OutlookCalIntegrationConfig)))))))))))))
                                                                                                 :<|> Named
                                                                                                        '("ipatch",
                                                                                                          OutlookCalIntegrationConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (Summary
                                                                                                               "Patch config for outlookCalIntegration"
                                                                                                             :> (CanThrow
                                                                                                                   ('MissingPermission
                                                                                                                      'Nothing)
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               TeamFeatureError
                                                                                                                             :> (CanThrowMany
                                                                                                                                   '[]
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("outlookCalIntegration"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                          OutlookCalIntegrationConfig)
                                                                                                                                                     :> Patch
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             OutlookCalIntegrationConfig)))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("iget",
                                                                                                     MlsE2EIdConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (Summary
                                                                                                          "Get config for mlsE2EId"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> ("teams"
                                                                                                                        :> (Capture
                                                                                                                              "tid"
                                                                                                                              TeamId
                                                                                                                            :> ("features"
                                                                                                                                :> ("mlsE2EId"
                                                                                                                                    :> Get
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            MlsE2EIdConfig))))))))))
                                                                                                 :<|> (Named
                                                                                                         '("iput",
                                                                                                           MlsE2EIdConfig)
                                                                                                         (Description
                                                                                                            ""
                                                                                                          :> (Summary
                                                                                                                "Put config for mlsE2EId"
                                                                                                              :> (CanThrow
                                                                                                                    ('MissingPermission
                                                                                                                       'Nothing)
                                                                                                                  :> (CanThrow
                                                                                                                        'NotATeamMember
                                                                                                                      :> (CanThrow
                                                                                                                            'TeamNotFound
                                                                                                                          :> (CanThrow
                                                                                                                                TeamFeatureError
                                                                                                                              :> (CanThrowMany
                                                                                                                                    '[]
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("mlsE2EId"
                                                                                                                                                  :> (ReqBody
                                                                                                                                                        '[JSON]
                                                                                                                                                        (Feature
                                                                                                                                                           MlsE2EIdConfig)
                                                                                                                                                      :> Put
                                                                                                                                                           '[JSON]
                                                                                                                                                           (LockableFeature
                                                                                                                                                              MlsE2EIdConfig)))))))))))))
                                                                                                       :<|> Named
                                                                                                              '("ipatch",
                                                                                                                MlsE2EIdConfig)
                                                                                                              (Description
                                                                                                                 ""
                                                                                                               :> (Summary
                                                                                                                     "Patch config for mlsE2EId"
                                                                                                                   :> (CanThrow
                                                                                                                         ('MissingPermission
                                                                                                                            'Nothing)
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     TeamFeatureError
                                                                                                                                   :> (CanThrowMany
                                                                                                                                         '[]
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("mlsE2EId"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                MlsE2EIdConfig)
                                                                                                                                                           :> Patch
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   MlsE2EIdConfig)))))))))))))))
                                                                                                :<|> ((Named
                                                                                                         '("iget",
                                                                                                           MlsMigrationConfig)
                                                                                                         (Description
                                                                                                            ""
                                                                                                          :> (Summary
                                                                                                                "Get config for mlsMigration"
                                                                                                              :> (CanThrow
                                                                                                                    ('MissingPermission
                                                                                                                       'Nothing)
                                                                                                                  :> (CanThrow
                                                                                                                        'NotATeamMember
                                                                                                                      :> (CanThrow
                                                                                                                            'TeamNotFound
                                                                                                                          :> ("teams"
                                                                                                                              :> (Capture
                                                                                                                                    "tid"
                                                                                                                                    TeamId
                                                                                                                                  :> ("features"
                                                                                                                                      :> ("mlsMigration"
                                                                                                                                          :> Get
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  MlsMigrationConfig))))))))))
                                                                                                       :<|> (Named
                                                                                                               '("iput",
                                                                                                                 MlsMigrationConfig)
                                                                                                               (Description
                                                                                                                  ""
                                                                                                                :> (Summary
                                                                                                                      "Put config for mlsMigration"
                                                                                                                    :> (CanThrow
                                                                                                                          ('MissingPermission
                                                                                                                             'Nothing)
                                                                                                                        :> (CanThrow
                                                                                                                              'NotATeamMember
                                                                                                                            :> (CanThrow
                                                                                                                                  'TeamNotFound
                                                                                                                                :> (CanThrow
                                                                                                                                      TeamFeatureError
                                                                                                                                    :> (CanThrowMany
                                                                                                                                          '[]
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("mlsMigration"
                                                                                                                                                        :> (ReqBody
                                                                                                                                                              '[JSON]
                                                                                                                                                              (Feature
                                                                                                                                                                 MlsMigrationConfig)
                                                                                                                                                            :> Put
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 (LockableFeature
                                                                                                                                                                    MlsMigrationConfig)))))))))))))
                                                                                                             :<|> Named
                                                                                                                    '("ipatch",
                                                                                                                      MlsMigrationConfig)
                                                                                                                    (Description
                                                                                                                       ""
                                                                                                                     :> (Summary
                                                                                                                           "Patch config for mlsMigration"
                                                                                                                         :> (CanThrow
                                                                                                                               ('MissingPermission
                                                                                                                                  'Nothing)
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotATeamMember
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TeamNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           TeamFeatureError
                                                                                                                                         :> (CanThrowMany
                                                                                                                                               '[]
                                                                                                                                             :> ("teams"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "tid"
                                                                                                                                                       TeamId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("mlsMigration"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                      MlsMigrationConfig)
                                                                                                                                                                 :> Patch
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         MlsMigrationConfig)))))))))))))))
                                                                                                      :<|> ((Named
                                                                                                               '("iget",
                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                               (Description
                                                                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                :> (Summary
                                                                                                                      "Get config for enforceFileDownloadLocation"
                                                                                                                    :> (CanThrow
                                                                                                                          ('MissingPermission
                                                                                                                             'Nothing)
                                                                                                                        :> (CanThrow
                                                                                                                              'NotATeamMember
                                                                                                                            :> (CanThrow
                                                                                                                                  'TeamNotFound
                                                                                                                                :> ("teams"
                                                                                                                                    :> (Capture
                                                                                                                                          "tid"
                                                                                                                                          TeamId
                                                                                                                                        :> ("features"
                                                                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                                                                :> Get
                                                                                                                                                     '[JSON]
                                                                                                                                                     (LockableFeature
                                                                                                                                                        EnforceFileDownloadLocationConfig))))))))))
                                                                                                             :<|> (Named
                                                                                                                     '("iput",
                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                     (Description
                                                                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                      :> (Summary
                                                                                                                            "Put config for enforceFileDownloadLocation"
                                                                                                                          :> (CanThrow
                                                                                                                                ('MissingPermission
                                                                                                                                   'Nothing)
                                                                                                                              :> (CanThrow
                                                                                                                                    'NotATeamMember
                                                                                                                                  :> (CanThrow
                                                                                                                                        'TeamNotFound
                                                                                                                                      :> (CanThrow
                                                                                                                                            TeamFeatureError
                                                                                                                                          :> (CanThrowMany
                                                                                                                                                '[]
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                                                                              :> (ReqBody
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (Feature
                                                                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                                                                  :> Put
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       (LockableFeature
                                                                                                                                                                          EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                   :<|> Named
                                                                                                                          '("ipatch",
                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                          (Description
                                                                                                                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                           :> (Summary
                                                                                                                                 "Patch config for enforceFileDownloadLocation"
                                                                                                                               :> (CanThrow
                                                                                                                                     ('MissingPermission
                                                                                                                                        'Nothing)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotATeamMember
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TeamNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 TeamFeatureError
                                                                                                                                               :> (CanThrowMany
                                                                                                                                                     '[]
                                                                                                                                                   :> ("teams"
                                                                                                                                                       :> (Capture
                                                                                                                                                             "tid"
                                                                                                                                                             TeamId
                                                                                                                                                           :> ("features"
                                                                                                                                                               :> ("enforceFileDownloadLocation"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                                                                       :> Patch
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("iget",
                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                    (Description
                                                                                                                       ""
                                                                                                                     :> (Summary
                                                                                                                           "Get config for limitedEventFanout"
                                                                                                                         :> (CanThrow
                                                                                                                               ('MissingPermission
                                                                                                                                  'Nothing)
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotATeamMember
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TeamNotFound
                                                                                                                                     :> ("teams"
                                                                                                                                         :> (Capture
                                                                                                                                               "tid"
                                                                                                                                               TeamId
                                                                                                                                             :> ("features"
                                                                                                                                                 :> ("limitedEventFanout"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             LimitedEventFanoutConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("iput",
                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                          (Description
                                                                                                                             ""
                                                                                                                           :> (Summary
                                                                                                                                 "Put config for limitedEventFanout"
                                                                                                                               :> (CanThrow
                                                                                                                                     ('MissingPermission
                                                                                                                                        'Nothing)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotATeamMember
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TeamNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 TeamFeatureError
                                                                                                                                               :> (CanThrowMany
                                                                                                                                                     '[]
                                                                                                                                                   :> ("teams"
                                                                                                                                                       :> (Capture
                                                                                                                                                             "tid"
                                                                                                                                                             TeamId
                                                                                                                                                           :> ("features"
                                                                                                                                                               :> ("limitedEventFanout"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (Feature
                                                                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                                                                       :> Put
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               LimitedEventFanoutConfig)))))))))))))
                                                                                                                        :<|> Named
                                                                                                                               '("ipatch",
                                                                                                                                 LimitedEventFanoutConfig)
                                                                                                                               (Description
                                                                                                                                  ""
                                                                                                                                :> (Summary
                                                                                                                                      "Patch config for limitedEventFanout"
                                                                                                                                    :> (CanThrow
                                                                                                                                          ('MissingPermission
                                                                                                                                             'Nothing)
                                                                                                                                        :> (CanThrow
                                                                                                                                              'NotATeamMember
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'TeamNotFound
                                                                                                                                                :> (CanThrow
                                                                                                                                                      TeamFeatureError
                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                          '[]
                                                                                                                                                        :> ("teams"
                                                                                                                                                            :> (Capture
                                                                                                                                                                  "tid"
                                                                                                                                                                  TeamId
                                                                                                                                                                :> ("features"
                                                                                                                                                                    :> ("limitedEventFanout"
                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeaturePatch
                                                                                                                                                                                 LimitedEventFanoutConfig)
                                                                                                                                                                            :> Patch
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                    LimitedEventFanoutConfig)))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", LegalholdConfig)
         (Description ""
          :> (Summary "Get config for legalhold"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("legalhold"
                                          :> Get '[JSON] (LockableFeature LegalholdConfig))))))))))
       :<|> (Named
               '("iput", LegalholdConfig)
               (Description ""
                :> (Summary "Put config for legalhold"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany
                                          '[ 'ActionDenied 'RemoveConversationMember,
                                             'CannotEnableLegalHoldServiceLargeTeam,
                                             'LegalHoldNotEnabled, 'LegalHoldDisableUnimplemented,
                                             'LegalHoldServiceNotRegistered,
                                             'UserLegalHoldIllegalOperation,
                                             'LegalHoldCouldNotBlockConnections]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("legalhold"
                                                        :> (ReqBody
                                                              '[JSON] (Feature LegalholdConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    LegalholdConfig)))))))))))))
             :<|> Named
                    '("ipatch", LegalholdConfig)
                    (Description ""
                     :> (Summary "Patch config for legalhold"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany
                                               '[ 'ActionDenied 'RemoveConversationMember,
                                                  'CannotEnableLegalHoldServiceLargeTeam,
                                                  'LegalHoldNotEnabled,
                                                  'LegalHoldDisableUnimplemented,
                                                  'LegalHoldServiceNotRegistered,
                                                  'UserLegalHoldIllegalOperation,
                                                  'LegalHoldCouldNotBlockConnections]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("legalhold"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      LegalholdConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         LegalholdConfig)))))))))))))))
      :<|> ((Named
               '("iget", SSOConfig)
               (Description ""
                :> (Summary "Get config for sso"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("sso"
                                                :> Get '[JSON] (LockableFeature SSOConfig))))))))))
             :<|> (Named
                     '("iput", SSOConfig)
                     (Description ""
                      :> (Summary "Put config for sso"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("sso"
                                                              :> (ReqBody
                                                                    '[JSON] (Feature SSOConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          SSOConfig)))))))))))))
                   :<|> Named
                          '("ipatch", SSOConfig)
                          (Description ""
                           :> (Summary "Patch config for sso"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("sso"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            SSOConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SSOConfig)))))))))))))))
            :<|> ((Named
                     '("iget", SearchVisibilityAvailableConfig)
                     (Description ""
                      :> (Summary "Get config for searchVisibility"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("searchVisibility"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              SearchVisibilityAvailableConfig))))))))))
                   :<|> (Named
                           '("iput", SearchVisibilityAvailableConfig)
                           (Description ""
                            :> (Summary "Put config for searchVisibility"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("searchVisibility"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             SearchVisibilityAvailableConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                SearchVisibilityAvailableConfig)))))))))))))
                         :<|> Named
                                '("ipatch", SearchVisibilityAvailableConfig)
                                (Description ""
                                 :> (Summary "Patch config for searchVisibility"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("searchVisibility"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  SearchVisibilityAvailableConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     SearchVisibilityAvailableConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", SearchVisibilityInboundConfig)
                           (Description ""
                            :> (Summary "Get config for searchVisibilityInbound"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("searchVisibilityInbound"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SearchVisibilityInboundConfig))))))))))
                         :<|> (Named
                                 '("iput", SearchVisibilityInboundConfig)
                                 (Description ""
                                  :> (Summary "Put config for searchVisibilityInbound"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("searchVisibilityInbound"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   SearchVisibilityInboundConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      SearchVisibilityInboundConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", SearchVisibilityInboundConfig)
                                      (Description ""
                                       :> (Summary "Patch config for searchVisibilityInbound"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("searchVisibilityInbound"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        SearchVisibilityInboundConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           SearchVisibilityInboundConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", ValidateSAMLEmailsConfig)
                                 (Description ""
                                  :> (Summary "Get config for validateSAMLemails"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("validateSAMLemails"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          ValidateSAMLEmailsConfig))))))))))
                               :<|> (Named
                                       '("iput", ValidateSAMLEmailsConfig)
                                       (Description ""
                                        :> (Summary "Put config for validateSAMLemails"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("validateSAMLemails"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         ValidateSAMLEmailsConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            ValidateSAMLEmailsConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", ValidateSAMLEmailsConfig)
                                            (Description ""
                                             :> (Summary "Patch config for validateSAMLemails"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("validateSAMLemails"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              ValidateSAMLEmailsConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 ValidateSAMLEmailsConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", DigitalSignaturesConfig)
                                       (Description ""
                                        :> (Summary "Get config for digitalSignatures"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("digitalSignatures"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                DigitalSignaturesConfig))))))))))
                                     :<|> (Named
                                             '("iput", DigitalSignaturesConfig)
                                             (Description ""
                                              :> (Summary "Put config for digitalSignatures"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("digitalSignatures"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               DigitalSignaturesConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  DigitalSignaturesConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", DigitalSignaturesConfig)
                                                  (Description ""
                                                   :> (Summary "Patch config for digitalSignatures"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("digitalSignatures"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    DigitalSignaturesConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       DigitalSignaturesConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", AppLockConfig)
                                             (Description ""
                                              :> (Summary "Get config for appLock"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("appLock"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      AppLockConfig))))))))))
                                           :<|> (Named
                                                   '("iput", AppLockConfig)
                                                   (Description ""
                                                    :> (Summary "Put config for appLock"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("appLock"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     AppLockConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        AppLockConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", AppLockConfig)
                                                        (Description ""
                                                         :> (Summary "Patch config for appLock"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("appLock"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          AppLockConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             AppLockConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", FileSharingConfig)
                                                   (Description ""
                                                    :> (Summary "Get config for fileSharing"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("fileSharing"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            FileSharingConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", FileSharingConfig)
                                                         (Description ""
                                                          :> (Summary "Put config for fileSharing"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("fileSharing"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           FileSharingConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              FileSharingConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch", FileSharingConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for fileSharing"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("fileSharing"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                FileSharingConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   FileSharingConfig)))))))))))))))
                                                :<|> (Named
                                                        '("iget", ClassifiedDomainsConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Get config for classifiedDomains"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("classifiedDomains"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 ClassifiedDomainsConfig))))))))))
                                                      :<|> ((Named
                                                               '("iget", ConferenceCallingConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Get config for conferenceCalling"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("conferenceCalling"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        ConferenceCallingConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput",
                                                                       ConferenceCallingConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for conferenceCalling"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("conferenceCalling"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       ConferenceCallingConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          ConferenceCallingConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            ConferenceCallingConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for conferenceCalling"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("conferenceCalling"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            ConferenceCallingConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               ConferenceCallingConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget",
                                                                       SelfDeletingMessagesConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Get config for selfDeletingMessages"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("selfDeletingMessages"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              SelfDeletingMessagesConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput",
                                                                             SelfDeletingMessagesConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Put config for selfDeletingMessages"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("selfDeletingMessages"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             SelfDeletingMessagesConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                SelfDeletingMessagesConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  SelfDeletingMessagesConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Patch config for selfDeletingMessages"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("selfDeletingMessages"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  SelfDeletingMessagesConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     SelfDeletingMessagesConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("iget",
                                                                             GuestLinksConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Get config for conversationGuestLinks"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("conversationGuestLinks"
                                                                                                            :> Get
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    GuestLinksConfig))))))))))
                                                                         :<|> (Named
                                                                                 '("iput",
                                                                                   GuestLinksConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Put config for conversationGuestLinks"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("conversationGuestLinks"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (Feature
                                                                                                                                   GuestLinksConfig)
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      GuestLinksConfig)))))))))))))
                                                                               :<|> Named
                                                                                      '("ipatch",
                                                                                        GuestLinksConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Patch config for conversationGuestLinks"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeaturePatch
                                                                                                                                        GuestLinksConfig)
                                                                                                                                   :> Patch
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           GuestLinksConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("iget",
                                                                                   SndFactorPasswordChallengeConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Get config for sndFactorPasswordChallenge"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("sndFactorPasswordChallenge"
                                                                                                                  :> Get
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          SndFactorPasswordChallengeConfig))))))))))
                                                                               :<|> (Named
                                                                                       '("iput",
                                                                                         SndFactorPasswordChallengeConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Put config for sndFactorPasswordChallenge"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> (CanThrow
                                                                                                              TeamFeatureError
                                                                                                            :> (CanThrowMany
                                                                                                                  '[]
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("sndFactorPasswordChallenge"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      (Feature
                                                                                                                                         SndFactorPasswordChallengeConfig)
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            SndFactorPasswordChallengeConfig)))))))))))))
                                                                                     :<|> Named
                                                                                            '("ipatch",
                                                                                              SndFactorPasswordChallengeConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (Summary
                                                                                                   "Patch config for sndFactorPasswordChallenge"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   TeamFeatureError
                                                                                                                 :> (CanThrowMany
                                                                                                                       '[]
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("sndFactorPasswordChallenge"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeaturePatch
                                                                                                                                              SndFactorPasswordChallengeConfig)
                                                                                                                                         :> Patch
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 SndFactorPasswordChallengeConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("iget",
                                                                                         MLSConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Get config for mls"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("mls"
                                                                                                                        :> Get
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                MLSConfig))))))))))
                                                                                     :<|> (Named
                                                                                             '("iput",
                                                                                               MLSConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Put config for mls"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> (CanThrow
                                                                                                                    TeamFeatureError
                                                                                                                  :> (CanThrowMany
                                                                                                                        '[]
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("mls"
                                                                                                                                      :> (ReqBody
                                                                                                                                            '[JSON]
                                                                                                                                            (Feature
                                                                                                                                               MLSConfig)
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  MLSConfig)))))))))))))
                                                                                           :<|> Named
                                                                                                  '("ipatch",
                                                                                                    MLSConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (Summary
                                                                                                         "Patch config for mls"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         TeamFeatureError
                                                                                                                       :> (CanThrowMany
                                                                                                                             '[]
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("mls"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                    MLSConfig)
                                                                                                                                               :> Patch
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       MLSConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("iget",
                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> ("teams"
                                                                                                                  :> (Capture
                                                                                                                        "tid"
                                                                                                                        TeamId
                                                                                                                      :> ("features"
                                                                                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                              :> Get
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                           :<|> (Named
                                                                                                   '("iput",
                                                                                                     ExposeInvitationURLsToTeamAdminConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (Summary
                                                                                                          "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> (CanThrow
                                                                                                                          TeamFeatureError
                                                                                                                        :> (CanThrowMany
                                                                                                                              '[]
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                            :> (ReqBody
                                                                                                                                                  '[JSON]
                                                                                                                                                  (Feature
                                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                :> Put
                                                                                                                                                     '[JSON]
                                                                                                                                                     (LockableFeature
                                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                 :<|> Named
                                                                                                        '("ipatch",
                                                                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (Summary
                                                                                                               "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                             :> (CanThrow
                                                                                                                   ('MissingPermission
                                                                                                                      'Nothing)
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               TeamFeatureError
                                                                                                                             :> (CanThrowMany
                                                                                                                                   '[]
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                     :> Patch
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("iget",
                                                                                                     OutlookCalIntegrationConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (Summary
                                                                                                          "Get config for outlookCalIntegration"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> ("teams"
                                                                                                                        :> (Capture
                                                                                                                              "tid"
                                                                                                                              TeamId
                                                                                                                            :> ("features"
                                                                                                                                :> ("outlookCalIntegration"
                                                                                                                                    :> Get
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            OutlookCalIntegrationConfig))))))))))
                                                                                                 :<|> (Named
                                                                                                         '("iput",
                                                                                                           OutlookCalIntegrationConfig)
                                                                                                         (Description
                                                                                                            ""
                                                                                                          :> (Summary
                                                                                                                "Put config for outlookCalIntegration"
                                                                                                              :> (CanThrow
                                                                                                                    ('MissingPermission
                                                                                                                       'Nothing)
                                                                                                                  :> (CanThrow
                                                                                                                        'NotATeamMember
                                                                                                                      :> (CanThrow
                                                                                                                            'TeamNotFound
                                                                                                                          :> (CanThrow
                                                                                                                                TeamFeatureError
                                                                                                                              :> (CanThrowMany
                                                                                                                                    '[]
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("outlookCalIntegration"
                                                                                                                                                  :> (ReqBody
                                                                                                                                                        '[JSON]
                                                                                                                                                        (Feature
                                                                                                                                                           OutlookCalIntegrationConfig)
                                                                                                                                                      :> Put
                                                                                                                                                           '[JSON]
                                                                                                                                                           (LockableFeature
                                                                                                                                                              OutlookCalIntegrationConfig)))))))))))))
                                                                                                       :<|> Named
                                                                                                              '("ipatch",
                                                                                                                OutlookCalIntegrationConfig)
                                                                                                              (Description
                                                                                                                 ""
                                                                                                               :> (Summary
                                                                                                                     "Patch config for outlookCalIntegration"
                                                                                                                   :> (CanThrow
                                                                                                                         ('MissingPermission
                                                                                                                            'Nothing)
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     TeamFeatureError
                                                                                                                                   :> (CanThrowMany
                                                                                                                                         '[]
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("outlookCalIntegration"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                OutlookCalIntegrationConfig)
                                                                                                                                                           :> Patch
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   OutlookCalIntegrationConfig)))))))))))))))
                                                                                                :<|> ((Named
                                                                                                         '("iget",
                                                                                                           MlsE2EIdConfig)
                                                                                                         (Description
                                                                                                            ""
                                                                                                          :> (Summary
                                                                                                                "Get config for mlsE2EId"
                                                                                                              :> (CanThrow
                                                                                                                    ('MissingPermission
                                                                                                                       'Nothing)
                                                                                                                  :> (CanThrow
                                                                                                                        'NotATeamMember
                                                                                                                      :> (CanThrow
                                                                                                                            'TeamNotFound
                                                                                                                          :> ("teams"
                                                                                                                              :> (Capture
                                                                                                                                    "tid"
                                                                                                                                    TeamId
                                                                                                                                  :> ("features"
                                                                                                                                      :> ("mlsE2EId"
                                                                                                                                          :> Get
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  MlsE2EIdConfig))))))))))
                                                                                                       :<|> (Named
                                                                                                               '("iput",
                                                                                                                 MlsE2EIdConfig)
                                                                                                               (Description
                                                                                                                  ""
                                                                                                                :> (Summary
                                                                                                                      "Put config for mlsE2EId"
                                                                                                                    :> (CanThrow
                                                                                                                          ('MissingPermission
                                                                                                                             'Nothing)
                                                                                                                        :> (CanThrow
                                                                                                                              'NotATeamMember
                                                                                                                            :> (CanThrow
                                                                                                                                  'TeamNotFound
                                                                                                                                :> (CanThrow
                                                                                                                                      TeamFeatureError
                                                                                                                                    :> (CanThrowMany
                                                                                                                                          '[]
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("mlsE2EId"
                                                                                                                                                        :> (ReqBody
                                                                                                                                                              '[JSON]
                                                                                                                                                              (Feature
                                                                                                                                                                 MlsE2EIdConfig)
                                                                                                                                                            :> Put
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 (LockableFeature
                                                                                                                                                                    MlsE2EIdConfig)))))))))))))
                                                                                                             :<|> Named
                                                                                                                    '("ipatch",
                                                                                                                      MlsE2EIdConfig)
                                                                                                                    (Description
                                                                                                                       ""
                                                                                                                     :> (Summary
                                                                                                                           "Patch config for mlsE2EId"
                                                                                                                         :> (CanThrow
                                                                                                                               ('MissingPermission
                                                                                                                                  'Nothing)
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotATeamMember
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TeamNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           TeamFeatureError
                                                                                                                                         :> (CanThrowMany
                                                                                                                                               '[]
                                                                                                                                             :> ("teams"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "tid"
                                                                                                                                                       TeamId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("mlsE2EId"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                      MlsE2EIdConfig)
                                                                                                                                                                 :> Patch
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         MlsE2EIdConfig)))))))))))))))
                                                                                                      :<|> ((Named
                                                                                                               '("iget",
                                                                                                                 MlsMigrationConfig)
                                                                                                               (Description
                                                                                                                  ""
                                                                                                                :> (Summary
                                                                                                                      "Get config for mlsMigration"
                                                                                                                    :> (CanThrow
                                                                                                                          ('MissingPermission
                                                                                                                             'Nothing)
                                                                                                                        :> (CanThrow
                                                                                                                              'NotATeamMember
                                                                                                                            :> (CanThrow
                                                                                                                                  'TeamNotFound
                                                                                                                                :> ("teams"
                                                                                                                                    :> (Capture
                                                                                                                                          "tid"
                                                                                                                                          TeamId
                                                                                                                                        :> ("features"
                                                                                                                                            :> ("mlsMigration"
                                                                                                                                                :> Get
                                                                                                                                                     '[JSON]
                                                                                                                                                     (LockableFeature
                                                                                                                                                        MlsMigrationConfig))))))))))
                                                                                                             :<|> (Named
                                                                                                                     '("iput",
                                                                                                                       MlsMigrationConfig)
                                                                                                                     (Description
                                                                                                                        ""
                                                                                                                      :> (Summary
                                                                                                                            "Put config for mlsMigration"
                                                                                                                          :> (CanThrow
                                                                                                                                ('MissingPermission
                                                                                                                                   'Nothing)
                                                                                                                              :> (CanThrow
                                                                                                                                    'NotATeamMember
                                                                                                                                  :> (CanThrow
                                                                                                                                        'TeamNotFound
                                                                                                                                      :> (CanThrow
                                                                                                                                            TeamFeatureError
                                                                                                                                          :> (CanThrowMany
                                                                                                                                                '[]
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("mlsMigration"
                                                                                                                                                              :> (ReqBody
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (Feature
                                                                                                                                                                       MlsMigrationConfig)
                                                                                                                                                                  :> Put
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       (LockableFeature
                                                                                                                                                                          MlsMigrationConfig)))))))))))))
                                                                                                                   :<|> Named
                                                                                                                          '("ipatch",
                                                                                                                            MlsMigrationConfig)
                                                                                                                          (Description
                                                                                                                             ""
                                                                                                                           :> (Summary
                                                                                                                                 "Patch config for mlsMigration"
                                                                                                                               :> (CanThrow
                                                                                                                                     ('MissingPermission
                                                                                                                                        'Nothing)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotATeamMember
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TeamNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 TeamFeatureError
                                                                                                                                               :> (CanThrowMany
                                                                                                                                                     '[]
                                                                                                                                                   :> ("teams"
                                                                                                                                                       :> (Capture
                                                                                                                                                             "tid"
                                                                                                                                                             TeamId
                                                                                                                                                           :> ("features"
                                                                                                                                                               :> ("mlsMigration"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                                            MlsMigrationConfig)
                                                                                                                                                                       :> Patch
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               MlsMigrationConfig)))))))))))))))
                                                                                                            :<|> ((Named
                                                                                                                     '("iget",
                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                     (Description
                                                                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                      :> (Summary
                                                                                                                            "Get config for enforceFileDownloadLocation"
                                                                                                                          :> (CanThrow
                                                                                                                                ('MissingPermission
                                                                                                                                   'Nothing)
                                                                                                                              :> (CanThrow
                                                                                                                                    'NotATeamMember
                                                                                                                                  :> (CanThrow
                                                                                                                                        'TeamNotFound
                                                                                                                                      :> ("teams"
                                                                                                                                          :> (Capture
                                                                                                                                                "tid"
                                                                                                                                                TeamId
                                                                                                                                              :> ("features"
                                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                                      :> Get
                                                                                                                                                           '[JSON]
                                                                                                                                                           (LockableFeature
                                                                                                                                                              EnforceFileDownloadLocationConfig))))))))))
                                                                                                                   :<|> (Named
                                                                                                                           '("iput",
                                                                                                                             EnforceFileDownloadLocationConfig)
                                                                                                                           (Description
                                                                                                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                            :> (Summary
                                                                                                                                  "Put config for enforceFileDownloadLocation"
                                                                                                                                :> (CanThrow
                                                                                                                                      ('MissingPermission
                                                                                                                                         'Nothing)
                                                                                                                                    :> (CanThrow
                                                                                                                                          'NotATeamMember
                                                                                                                                        :> (CanThrow
                                                                                                                                              'TeamNotFound
                                                                                                                                            :> (CanThrow
                                                                                                                                                  TeamFeatureError
                                                                                                                                                :> (CanThrowMany
                                                                                                                                                      '[]
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          (Feature
                                                                                                                                                                             EnforceFileDownloadLocationConfig)
                                                                                                                                                                        :> Put
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                         :<|> Named
                                                                                                                                '("ipatch",
                                                                                                                                  EnforceFileDownloadLocationConfig)
                                                                                                                                (Description
                                                                                                                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                 :> (Summary
                                                                                                                                       "Patch config for enforceFileDownloadLocation"
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('MissingPermission
                                                                                                                                              'Nothing)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NotATeamMember
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'TeamNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       TeamFeatureError
                                                                                                                                                     :> (CanThrowMany
                                                                                                                                                           '[]
                                                                                                                                                         :> ("teams"
                                                                                                                                                             :> (Capture
                                                                                                                                                                   "tid"
                                                                                                                                                                   TeamId
                                                                                                                                                                 :> ("features"
                                                                                                                                                                     :> ("enforceFileDownloadLocation"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeaturePatch
                                                                                                                                                                                  EnforceFileDownloadLocationConfig)
                                                                                                                                                                             :> Patch
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("iget",
                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                          (Description
                                                                                                                             ""
                                                                                                                           :> (Summary
                                                                                                                                 "Get config for limitedEventFanout"
                                                                                                                               :> (CanThrow
                                                                                                                                     ('MissingPermission
                                                                                                                                        'Nothing)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotATeamMember
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TeamNotFound
                                                                                                                                           :> ("teams"
                                                                                                                                               :> (Capture
                                                                                                                                                     "tid"
                                                                                                                                                     TeamId
                                                                                                                                                   :> ("features"
                                                                                                                                                       :> ("limitedEventFanout"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   LimitedEventFanoutConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("iput",
                                                                                                                                  LimitedEventFanoutConfig)
                                                                                                                                (Description
                                                                                                                                   ""
                                                                                                                                 :> (Summary
                                                                                                                                       "Put config for limitedEventFanout"
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('MissingPermission
                                                                                                                                              'Nothing)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NotATeamMember
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'TeamNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       TeamFeatureError
                                                                                                                                                     :> (CanThrowMany
                                                                                                                                                           '[]
                                                                                                                                                         :> ("teams"
                                                                                                                                                             :> (Capture
                                                                                                                                                                   "tid"
                                                                                                                                                                   TeamId
                                                                                                                                                                 :> ("features"
                                                                                                                                                                     :> ("limitedEventFanout"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (Feature
                                                                                                                                                                                  LimitedEventFanoutConfig)
                                                                                                                                                                             :> Put
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     LimitedEventFanoutConfig)))))))))))))
                                                                                                                              :<|> Named
                                                                                                                                     '("ipatch",
                                                                                                                                       LimitedEventFanoutConfig)
                                                                                                                                     (Description
                                                                                                                                        ""
                                                                                                                                      :> (Summary
                                                                                                                                            "Patch config for limitedEventFanout"
                                                                                                                                          :> (CanThrow
                                                                                                                                                ('MissingPermission
                                                                                                                                                   'Nothing)
                                                                                                                                              :> (CanThrow
                                                                                                                                                    'NotATeamMember
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'TeamNotFound
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            TeamFeatureError
                                                                                                                                                          :> (CanThrowMany
                                                                                                                                                                '[]
                                                                                                                                                              :> ("teams"
                                                                                                                                                                  :> (Capture
                                                                                                                                                                        "tid"
                                                                                                                                                                        TeamId
                                                                                                                                                                      :> ("features"
                                                                                                                                                                          :> ("limitedEventFanout"
                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeaturePatch
                                                                                                                                                                                       LimitedEventFanoutConfig)
                                                                                                                                                                                  :> Patch
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                          LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", SSOConfig)
     (Description ""
      :> (Summary "Get config for sso"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("sso" :> Get '[JSON] (LockableFeature SSOConfig))))))))))
   :<|> (Named
           '("iput", SSOConfig)
           (Description ""
            :> (Summary "Put config for sso"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("sso"
                                                    :> (ReqBody '[JSON] (Feature SSOConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature SSOConfig)))))))))))))
         :<|> Named
                '("ipatch", SSOConfig)
                (Description ""
                 :> (Summary "Patch config for sso"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("sso"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch SSOConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SSOConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", SSOConfig)
     (Description (FeatureAPIDesc SSOConfig)
      :> (Summary
            (AppendSymbol "Get config for " (FeatureSymbol SSOConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol SSOConfig
                                      :> Get '[JSON] (LockableFeature SSOConfig))))))))))
   :<|> (Named
           '("iput", SSOConfig)
           (Description (FeatureAPIDesc SSOConfig)
            :> (Summary
                  (AppendSymbol "Put config for " (FeatureSymbol SSOConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors SSOConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol SSOConfig
                                                    :> (ReqBody '[JSON] (Feature SSOConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature SSOConfig)))))))))))))
         :<|> Named
                '("ipatch", SSOConfig)
                (Description (FeatureAPIDesc SSOConfig)
                 :> (Summary
                       (AppendSymbol "Patch config for " (FeatureSymbol SSOConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany (FeatureErrors SSOConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol SSOConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch SSOConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SSOConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", SSOConfig)
     (Description ""
      :> (Summary "Get config for sso"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("sso" :> Get '[JSON] (LockableFeature SSOConfig))))))))))
   :<|> (Named
           '("iput", SSOConfig)
           (Description ""
            :> (Summary "Put config for sso"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("sso"
                                                    :> (ReqBody '[JSON] (Feature SSOConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature SSOConfig)))))))))))))
         :<|> Named
                '("ipatch", SSOConfig)
                (Description ""
                 :> (Summary "Patch config for sso"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("sso"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch SSOConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SSOConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", SearchVisibilityAvailableConfig)
         (Description ""
          :> (Summary "Get config for searchVisibility"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("searchVisibility"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SearchVisibilityAvailableConfig))))))))))
       :<|> (Named
               '("iput", SearchVisibilityAvailableConfig)
               (Description ""
                :> (Summary "Put config for searchVisibility"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("searchVisibility"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature
                                                                 SearchVisibilityAvailableConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SearchVisibilityAvailableConfig)))))))))))))
             :<|> Named
                    '("ipatch", SearchVisibilityAvailableConfig)
                    (Description ""
                     :> (Summary "Patch config for searchVisibility"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("searchVisibility"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      SearchVisibilityAvailableConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SearchVisibilityAvailableConfig)))))))))))))))
      :<|> ((Named
               '("iget", SearchVisibilityInboundConfig)
               (Description ""
                :> (Summary "Get config for searchVisibilityInbound"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("searchVisibilityInbound"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        SearchVisibilityInboundConfig))))))))))
             :<|> (Named
                     '("iput", SearchVisibilityInboundConfig)
                     (Description ""
                      :> (Summary "Put config for searchVisibilityInbound"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("searchVisibilityInbound"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       SearchVisibilityInboundConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          SearchVisibilityInboundConfig)))))))))))))
                   :<|> Named
                          '("ipatch", SearchVisibilityInboundConfig)
                          (Description ""
                           :> (Summary "Patch config for searchVisibilityInbound"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("searchVisibilityInbound"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            SearchVisibilityInboundConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SearchVisibilityInboundConfig)))))))))))))))
            :<|> ((Named
                     '("iget", ValidateSAMLEmailsConfig)
                     (Description ""
                      :> (Summary "Get config for validateSAMLemails"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("validateSAMLemails"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              ValidateSAMLEmailsConfig))))))))))
                   :<|> (Named
                           '("iput", ValidateSAMLEmailsConfig)
                           (Description ""
                            :> (Summary "Put config for validateSAMLemails"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("validateSAMLemails"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             ValidateSAMLEmailsConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                ValidateSAMLEmailsConfig)))))))))))))
                         :<|> Named
                                '("ipatch", ValidateSAMLEmailsConfig)
                                (Description ""
                                 :> (Summary "Patch config for validateSAMLemails"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("validateSAMLemails"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  ValidateSAMLEmailsConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     ValidateSAMLEmailsConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", DigitalSignaturesConfig)
                           (Description ""
                            :> (Summary "Get config for digitalSignatures"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("digitalSignatures"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    DigitalSignaturesConfig))))))))))
                         :<|> (Named
                                 '("iput", DigitalSignaturesConfig)
                                 (Description ""
                                  :> (Summary "Put config for digitalSignatures"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("digitalSignatures"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   DigitalSignaturesConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      DigitalSignaturesConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", DigitalSignaturesConfig)
                                      (Description ""
                                       :> (Summary "Patch config for digitalSignatures"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("digitalSignatures"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        DigitalSignaturesConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           DigitalSignaturesConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", AppLockConfig)
                                 (Description ""
                                  :> (Summary "Get config for appLock"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("appLock"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          AppLockConfig))))))))))
                               :<|> (Named
                                       '("iput", AppLockConfig)
                                       (Description ""
                                        :> (Summary "Put config for appLock"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("appLock"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         AppLockConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            AppLockConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", AppLockConfig)
                                            (Description ""
                                             :> (Summary "Patch config for appLock"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("appLock"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              AppLockConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 AppLockConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", FileSharingConfig)
                                       (Description ""
                                        :> (Summary "Get config for fileSharing"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("fileSharing"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                FileSharingConfig))))))))))
                                     :<|> (Named
                                             '("iput", FileSharingConfig)
                                             (Description ""
                                              :> (Summary "Put config for fileSharing"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("fileSharing"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               FileSharingConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  FileSharingConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", FileSharingConfig)
                                                  (Description ""
                                                   :> (Summary "Patch config for fileSharing"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("fileSharing"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    FileSharingConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       FileSharingConfig)))))))))))))))
                                    :<|> (Named
                                            '("iget", ClassifiedDomainsConfig)
                                            (Description ""
                                             :> (Summary "Get config for classifiedDomains"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("classifiedDomains"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     ClassifiedDomainsConfig))))))))))
                                          :<|> ((Named
                                                   '("iget", ConferenceCallingConfig)
                                                   (Description ""
                                                    :> (Summary "Get config for conferenceCalling"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("conferenceCalling"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            ConferenceCallingConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", ConferenceCallingConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Put config for conferenceCalling"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("conferenceCalling"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           ConferenceCallingConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              ConferenceCallingConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch", ConferenceCallingConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for conferenceCalling"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("conferenceCalling"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                ConferenceCallingConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   ConferenceCallingConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget", SelfDeletingMessagesConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Get config for selfDeletingMessages"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("selfDeletingMessages"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  SelfDeletingMessagesConfig))))))))))
                                                       :<|> (Named
                                                               '("iput", SelfDeletingMessagesConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for selfDeletingMessages"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("selfDeletingMessages"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 SelfDeletingMessagesConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    SelfDeletingMessagesConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch",
                                                                      SelfDeletingMessagesConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for selfDeletingMessages"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("selfDeletingMessages"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      SelfDeletingMessagesConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         SelfDeletingMessagesConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget", GuestLinksConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Get config for conversationGuestLinks"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("conversationGuestLinks"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        GuestLinksConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput", GuestLinksConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for conversationGuestLinks"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("conversationGuestLinks"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       GuestLinksConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          GuestLinksConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            GuestLinksConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for conversationGuestLinks"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("conversationGuestLinks"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            GuestLinksConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               GuestLinksConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget",
                                                                       SndFactorPasswordChallengeConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Get config for sndFactorPasswordChallenge"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("sndFactorPasswordChallenge"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              SndFactorPasswordChallengeConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput",
                                                                             SndFactorPasswordChallengeConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Put config for sndFactorPasswordChallenge"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("sndFactorPasswordChallenge"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             SndFactorPasswordChallengeConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                SndFactorPasswordChallengeConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  SndFactorPasswordChallengeConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Patch config for sndFactorPasswordChallenge"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("sndFactorPasswordChallenge"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     SndFactorPasswordChallengeConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("iget", MLSConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Get config for mls"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("mls"
                                                                                                            :> Get
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    MLSConfig))))))))))
                                                                         :<|> (Named
                                                                                 '("iput",
                                                                                   MLSConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Put config for mls"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mls"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (Feature
                                                                                                                                   MLSConfig)
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      MLSConfig)))))))))))))
                                                                               :<|> Named
                                                                                      '("ipatch",
                                                                                        MLSConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Patch config for mls"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("mls"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeaturePatch
                                                                                                                                        MLSConfig)
                                                                                                                                   :> Patch
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           MLSConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("iget",
                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                  :> Get
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                               :<|> (Named
                                                                                       '("iput",
                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> (CanThrow
                                                                                                              TeamFeatureError
                                                                                                            :> (CanThrowMany
                                                                                                                  '[]
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      (Feature
                                                                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                     :<|> Named
                                                                                            '("ipatch",
                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (Summary
                                                                                                   "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   TeamFeatureError
                                                                                                                 :> (CanThrowMany
                                                                                                                       '[]
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeaturePatch
                                                                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                         :> Patch
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("iget",
                                                                                         OutlookCalIntegrationConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Get config for outlookCalIntegration"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("outlookCalIntegration"
                                                                                                                        :> Get
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                OutlookCalIntegrationConfig))))))))))
                                                                                     :<|> (Named
                                                                                             '("iput",
                                                                                               OutlookCalIntegrationConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Put config for outlookCalIntegration"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> (CanThrow
                                                                                                                    TeamFeatureError
                                                                                                                  :> (CanThrowMany
                                                                                                                        '[]
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("outlookCalIntegration"
                                                                                                                                      :> (ReqBody
                                                                                                                                            '[JSON]
                                                                                                                                            (Feature
                                                                                                                                               OutlookCalIntegrationConfig)
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  OutlookCalIntegrationConfig)))))))))))))
                                                                                           :<|> Named
                                                                                                  '("ipatch",
                                                                                                    OutlookCalIntegrationConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (Summary
                                                                                                         "Patch config for outlookCalIntegration"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         TeamFeatureError
                                                                                                                       :> (CanThrowMany
                                                                                                                             '[]
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("outlookCalIntegration"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                    OutlookCalIntegrationConfig)
                                                                                                                                               :> Patch
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       OutlookCalIntegrationConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("iget",
                                                                                               MlsE2EIdConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Get config for mlsE2EId"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> ("teams"
                                                                                                                  :> (Capture
                                                                                                                        "tid"
                                                                                                                        TeamId
                                                                                                                      :> ("features"
                                                                                                                          :> ("mlsE2EId"
                                                                                                                              :> Get
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      MlsE2EIdConfig))))))))))
                                                                                           :<|> (Named
                                                                                                   '("iput",
                                                                                                     MlsE2EIdConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (Summary
                                                                                                          "Put config for mlsE2EId"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> (CanThrow
                                                                                                                          TeamFeatureError
                                                                                                                        :> (CanThrowMany
                                                                                                                              '[]
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("mlsE2EId"
                                                                                                                                            :> (ReqBody
                                                                                                                                                  '[JSON]
                                                                                                                                                  (Feature
                                                                                                                                                     MlsE2EIdConfig)
                                                                                                                                                :> Put
                                                                                                                                                     '[JSON]
                                                                                                                                                     (LockableFeature
                                                                                                                                                        MlsE2EIdConfig)))))))))))))
                                                                                                 :<|> Named
                                                                                                        '("ipatch",
                                                                                                          MlsE2EIdConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (Summary
                                                                                                               "Patch config for mlsE2EId"
                                                                                                             :> (CanThrow
                                                                                                                   ('MissingPermission
                                                                                                                      'Nothing)
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               TeamFeatureError
                                                                                                                             :> (CanThrowMany
                                                                                                                                   '[]
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("mlsE2EId"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                          MlsE2EIdConfig)
                                                                                                                                                     :> Patch
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             MlsE2EIdConfig)))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("iget",
                                                                                                     MlsMigrationConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (Summary
                                                                                                          "Get config for mlsMigration"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> ("teams"
                                                                                                                        :> (Capture
                                                                                                                              "tid"
                                                                                                                              TeamId
                                                                                                                            :> ("features"
                                                                                                                                :> ("mlsMigration"
                                                                                                                                    :> Get
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            MlsMigrationConfig))))))))))
                                                                                                 :<|> (Named
                                                                                                         '("iput",
                                                                                                           MlsMigrationConfig)
                                                                                                         (Description
                                                                                                            ""
                                                                                                          :> (Summary
                                                                                                                "Put config for mlsMigration"
                                                                                                              :> (CanThrow
                                                                                                                    ('MissingPermission
                                                                                                                       'Nothing)
                                                                                                                  :> (CanThrow
                                                                                                                        'NotATeamMember
                                                                                                                      :> (CanThrow
                                                                                                                            'TeamNotFound
                                                                                                                          :> (CanThrow
                                                                                                                                TeamFeatureError
                                                                                                                              :> (CanThrowMany
                                                                                                                                    '[]
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("mlsMigration"
                                                                                                                                                  :> (ReqBody
                                                                                                                                                        '[JSON]
                                                                                                                                                        (Feature
                                                                                                                                                           MlsMigrationConfig)
                                                                                                                                                      :> Put
                                                                                                                                                           '[JSON]
                                                                                                                                                           (LockableFeature
                                                                                                                                                              MlsMigrationConfig)))))))))))))
                                                                                                       :<|> Named
                                                                                                              '("ipatch",
                                                                                                                MlsMigrationConfig)
                                                                                                              (Description
                                                                                                                 ""
                                                                                                               :> (Summary
                                                                                                                     "Patch config for mlsMigration"
                                                                                                                   :> (CanThrow
                                                                                                                         ('MissingPermission
                                                                                                                            'Nothing)
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     TeamFeatureError
                                                                                                                                   :> (CanThrowMany
                                                                                                                                         '[]
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("mlsMigration"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                MlsMigrationConfig)
                                                                                                                                                           :> Patch
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   MlsMigrationConfig)))))))))))))))
                                                                                                :<|> ((Named
                                                                                                         '("iget",
                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                         (Description
                                                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                          :> (Summary
                                                                                                                "Get config for enforceFileDownloadLocation"
                                                                                                              :> (CanThrow
                                                                                                                    ('MissingPermission
                                                                                                                       'Nothing)
                                                                                                                  :> (CanThrow
                                                                                                                        'NotATeamMember
                                                                                                                      :> (CanThrow
                                                                                                                            'TeamNotFound
                                                                                                                          :> ("teams"
                                                                                                                              :> (Capture
                                                                                                                                    "tid"
                                                                                                                                    TeamId
                                                                                                                                  :> ("features"
                                                                                                                                      :> ("enforceFileDownloadLocation"
                                                                                                                                          :> Get
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  EnforceFileDownloadLocationConfig))))))))))
                                                                                                       :<|> (Named
                                                                                                               '("iput",
                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                               (Description
                                                                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                :> (Summary
                                                                                                                      "Put config for enforceFileDownloadLocation"
                                                                                                                    :> (CanThrow
                                                                                                                          ('MissingPermission
                                                                                                                             'Nothing)
                                                                                                                        :> (CanThrow
                                                                                                                              'NotATeamMember
                                                                                                                            :> (CanThrow
                                                                                                                                  'TeamNotFound
                                                                                                                                :> (CanThrow
                                                                                                                                      TeamFeatureError
                                                                                                                                    :> (CanThrowMany
                                                                                                                                          '[]
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                                                                        :> (ReqBody
                                                                                                                                                              '[JSON]
                                                                                                                                                              (Feature
                                                                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                                                                            :> Put
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 (LockableFeature
                                                                                                                                                                    EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                             :<|> Named
                                                                                                                    '("ipatch",
                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                    (Description
                                                                                                                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                     :> (Summary
                                                                                                                           "Patch config for enforceFileDownloadLocation"
                                                                                                                         :> (CanThrow
                                                                                                                               ('MissingPermission
                                                                                                                                  'Nothing)
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotATeamMember
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TeamNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           TeamFeatureError
                                                                                                                                         :> (CanThrowMany
                                                                                                                                               '[]
                                                                                                                                             :> ("teams"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "tid"
                                                                                                                                                       TeamId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("enforceFileDownloadLocation"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                                                                 :> Patch
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("iget",
                                                                                                                LimitedEventFanoutConfig)
                                                                                                              (Description
                                                                                                                 ""
                                                                                                               :> (Summary
                                                                                                                     "Get config for limitedEventFanout"
                                                                                                                   :> (CanThrow
                                                                                                                         ('MissingPermission
                                                                                                                            'Nothing)
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> ("teams"
                                                                                                                                   :> (Capture
                                                                                                                                         "tid"
                                                                                                                                         TeamId
                                                                                                                                       :> ("features"
                                                                                                                                           :> ("limitedEventFanout"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       LimitedEventFanoutConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("iput",
                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                    (Description
                                                                                                                       ""
                                                                                                                     :> (Summary
                                                                                                                           "Put config for limitedEventFanout"
                                                                                                                         :> (CanThrow
                                                                                                                               ('MissingPermission
                                                                                                                                  'Nothing)
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotATeamMember
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TeamNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           TeamFeatureError
                                                                                                                                         :> (CanThrowMany
                                                                                                                                               '[]
                                                                                                                                             :> ("teams"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "tid"
                                                                                                                                                       TeamId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("limitedEventFanout"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (Feature
                                                                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                                                                 :> Put
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         LimitedEventFanoutConfig)))))))))))))
                                                                                                                  :<|> Named
                                                                                                                         '("ipatch",
                                                                                                                           LimitedEventFanoutConfig)
                                                                                                                         (Description
                                                                                                                            ""
                                                                                                                          :> (Summary
                                                                                                                                "Patch config for limitedEventFanout"
                                                                                                                              :> (CanThrow
                                                                                                                                    ('MissingPermission
                                                                                                                                       'Nothing)
                                                                                                                                  :> (CanThrow
                                                                                                                                        'NotATeamMember
                                                                                                                                      :> (CanThrow
                                                                                                                                            'TeamNotFound
                                                                                                                                          :> (CanThrow
                                                                                                                                                TeamFeatureError
                                                                                                                                              :> (CanThrowMany
                                                                                                                                                    '[]
                                                                                                                                                  :> ("teams"
                                                                                                                                                      :> (Capture
                                                                                                                                                            "tid"
                                                                                                                                                            TeamId
                                                                                                                                                          :> ("features"
                                                                                                                                                              :> ("limitedEventFanout"
                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeaturePatch
                                                                                                                                                                           LimitedEventFanoutConfig)
                                                                                                                                                                      :> Patch
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeature
                                                                                                                                                                              LimitedEventFanoutConfig))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", SSOConfig)
         (Description ""
          :> (Summary "Get config for sso"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("sso" :> Get '[JSON] (LockableFeature SSOConfig))))))))))
       :<|> (Named
               '("iput", SSOConfig)
               (Description ""
                :> (Summary "Put config for sso"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("sso"
                                                        :> (ReqBody '[JSON] (Feature SSOConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SSOConfig)))))))))))))
             :<|> Named
                    '("ipatch", SSOConfig)
                    (Description ""
                     :> (Summary "Patch config for sso"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("sso"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch SSOConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SSOConfig)))))))))))))))
      :<|> ((Named
               '("iget", SearchVisibilityAvailableConfig)
               (Description ""
                :> (Summary "Get config for searchVisibility"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("searchVisibility"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        SearchVisibilityAvailableConfig))))))))))
             :<|> (Named
                     '("iput", SearchVisibilityAvailableConfig)
                     (Description ""
                      :> (Summary "Put config for searchVisibility"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("searchVisibility"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       SearchVisibilityAvailableConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          SearchVisibilityAvailableConfig)))))))))))))
                   :<|> Named
                          '("ipatch", SearchVisibilityAvailableConfig)
                          (Description ""
                           :> (Summary "Patch config for searchVisibility"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("searchVisibility"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            SearchVisibilityAvailableConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SearchVisibilityAvailableConfig)))))))))))))))
            :<|> ((Named
                     '("iget", SearchVisibilityInboundConfig)
                     (Description ""
                      :> (Summary "Get config for searchVisibilityInbound"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("searchVisibilityInbound"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              SearchVisibilityInboundConfig))))))))))
                   :<|> (Named
                           '("iput", SearchVisibilityInboundConfig)
                           (Description ""
                            :> (Summary "Put config for searchVisibilityInbound"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("searchVisibilityInbound"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             SearchVisibilityInboundConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                SearchVisibilityInboundConfig)))))))))))))
                         :<|> Named
                                '("ipatch", SearchVisibilityInboundConfig)
                                (Description ""
                                 :> (Summary "Patch config for searchVisibilityInbound"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("searchVisibilityInbound"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  SearchVisibilityInboundConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     SearchVisibilityInboundConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", ValidateSAMLEmailsConfig)
                           (Description ""
                            :> (Summary "Get config for validateSAMLemails"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("validateSAMLemails"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    ValidateSAMLEmailsConfig))))))))))
                         :<|> (Named
                                 '("iput", ValidateSAMLEmailsConfig)
                                 (Description ""
                                  :> (Summary "Put config for validateSAMLemails"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("validateSAMLemails"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   ValidateSAMLEmailsConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      ValidateSAMLEmailsConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", ValidateSAMLEmailsConfig)
                                      (Description ""
                                       :> (Summary "Patch config for validateSAMLemails"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("validateSAMLemails"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        ValidateSAMLEmailsConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           ValidateSAMLEmailsConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", DigitalSignaturesConfig)
                                 (Description ""
                                  :> (Summary "Get config for digitalSignatures"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("digitalSignatures"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          DigitalSignaturesConfig))))))))))
                               :<|> (Named
                                       '("iput", DigitalSignaturesConfig)
                                       (Description ""
                                        :> (Summary "Put config for digitalSignatures"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("digitalSignatures"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         DigitalSignaturesConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            DigitalSignaturesConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", DigitalSignaturesConfig)
                                            (Description ""
                                             :> (Summary "Patch config for digitalSignatures"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("digitalSignatures"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              DigitalSignaturesConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 DigitalSignaturesConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", AppLockConfig)
                                       (Description ""
                                        :> (Summary "Get config for appLock"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("appLock"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                AppLockConfig))))))))))
                                     :<|> (Named
                                             '("iput", AppLockConfig)
                                             (Description ""
                                              :> (Summary "Put config for appLock"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("appLock"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               AppLockConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  AppLockConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", AppLockConfig)
                                                  (Description ""
                                                   :> (Summary "Patch config for appLock"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("appLock"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    AppLockConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       AppLockConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", FileSharingConfig)
                                             (Description ""
                                              :> (Summary "Get config for fileSharing"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("fileSharing"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      FileSharingConfig))))))))))
                                           :<|> (Named
                                                   '("iput", FileSharingConfig)
                                                   (Description ""
                                                    :> (Summary "Put config for fileSharing"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("fileSharing"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     FileSharingConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        FileSharingConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", FileSharingConfig)
                                                        (Description ""
                                                         :> (Summary "Patch config for fileSharing"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("fileSharing"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          FileSharingConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             FileSharingConfig)))))))))))))))
                                          :<|> (Named
                                                  '("iget", ClassifiedDomainsConfig)
                                                  (Description ""
                                                   :> (Summary "Get config for classifiedDomains"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("classifiedDomains"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           ClassifiedDomainsConfig))))))))))
                                                :<|> ((Named
                                                         '("iget", ConferenceCallingConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Get config for conferenceCalling"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("conferenceCalling"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  ConferenceCallingConfig))))))))))
                                                       :<|> (Named
                                                               '("iput", ConferenceCallingConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for conferenceCalling"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("conferenceCalling"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 ConferenceCallingConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    ConferenceCallingConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch",
                                                                      ConferenceCallingConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for conferenceCalling"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("conferenceCalling"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      ConferenceCallingConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         ConferenceCallingConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget", SelfDeletingMessagesConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Get config for selfDeletingMessages"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("selfDeletingMessages"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        SelfDeletingMessagesConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput",
                                                                       SelfDeletingMessagesConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for selfDeletingMessages"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("selfDeletingMessages"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       SelfDeletingMessagesConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          SelfDeletingMessagesConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            SelfDeletingMessagesConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for selfDeletingMessages"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("selfDeletingMessages"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            SelfDeletingMessagesConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               SelfDeletingMessagesConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget", GuestLinksConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Get config for conversationGuestLinks"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("conversationGuestLinks"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              GuestLinksConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput",
                                                                             GuestLinksConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Put config for conversationGuestLinks"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("conversationGuestLinks"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             GuestLinksConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                GuestLinksConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  GuestLinksConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Patch config for conversationGuestLinks"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  GuestLinksConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     GuestLinksConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("iget",
                                                                             SndFactorPasswordChallengeConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Get config for sndFactorPasswordChallenge"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("sndFactorPasswordChallenge"
                                                                                                            :> Get
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    SndFactorPasswordChallengeConfig))))))))))
                                                                         :<|> (Named
                                                                                 '("iput",
                                                                                   SndFactorPasswordChallengeConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Put config for sndFactorPasswordChallenge"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("sndFactorPasswordChallenge"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (Feature
                                                                                                                                   SndFactorPasswordChallengeConfig)
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      SndFactorPasswordChallengeConfig)))))))))))))
                                                                               :<|> Named
                                                                                      '("ipatch",
                                                                                        SndFactorPasswordChallengeConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Patch config for sndFactorPasswordChallenge"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeaturePatch
                                                                                                                                        SndFactorPasswordChallengeConfig)
                                                                                                                                   :> Patch
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           SndFactorPasswordChallengeConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("iget",
                                                                                   MLSConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Get config for mls"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("mls"
                                                                                                                  :> Get
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          MLSConfig))))))))))
                                                                               :<|> (Named
                                                                                       '("iput",
                                                                                         MLSConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Put config for mls"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> (CanThrow
                                                                                                              TeamFeatureError
                                                                                                            :> (CanThrowMany
                                                                                                                  '[]
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mls"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      (Feature
                                                                                                                                         MLSConfig)
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            MLSConfig)))))))))))))
                                                                                     :<|> Named
                                                                                            '("ipatch",
                                                                                              MLSConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (Summary
                                                                                                   "Patch config for mls"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   TeamFeatureError
                                                                                                                 :> (CanThrowMany
                                                                                                                       '[]
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("mls"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeaturePatch
                                                                                                                                              MLSConfig)
                                                                                                                                         :> Patch
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 MLSConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("iget",
                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                        :> Get
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                     :<|> (Named
                                                                                             '("iput",
                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> (CanThrow
                                                                                                                    TeamFeatureError
                                                                                                                  :> (CanThrowMany
                                                                                                                        '[]
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                      :> (ReqBody
                                                                                                                                            '[JSON]
                                                                                                                                            (Feature
                                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                           :<|> Named
                                                                                                  '("ipatch",
                                                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (Summary
                                                                                                         "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         TeamFeatureError
                                                                                                                       :> (CanThrowMany
                                                                                                                             '[]
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                               :> Patch
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("iget",
                                                                                               OutlookCalIntegrationConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Get config for outlookCalIntegration"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> ("teams"
                                                                                                                  :> (Capture
                                                                                                                        "tid"
                                                                                                                        TeamId
                                                                                                                      :> ("features"
                                                                                                                          :> ("outlookCalIntegration"
                                                                                                                              :> Get
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      OutlookCalIntegrationConfig))))))))))
                                                                                           :<|> (Named
                                                                                                   '("iput",
                                                                                                     OutlookCalIntegrationConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (Summary
                                                                                                          "Put config for outlookCalIntegration"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> (CanThrow
                                                                                                                          TeamFeatureError
                                                                                                                        :> (CanThrowMany
                                                                                                                              '[]
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("outlookCalIntegration"
                                                                                                                                            :> (ReqBody
                                                                                                                                                  '[JSON]
                                                                                                                                                  (Feature
                                                                                                                                                     OutlookCalIntegrationConfig)
                                                                                                                                                :> Put
                                                                                                                                                     '[JSON]
                                                                                                                                                     (LockableFeature
                                                                                                                                                        OutlookCalIntegrationConfig)))))))))))))
                                                                                                 :<|> Named
                                                                                                        '("ipatch",
                                                                                                          OutlookCalIntegrationConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (Summary
                                                                                                               "Patch config for outlookCalIntegration"
                                                                                                             :> (CanThrow
                                                                                                                   ('MissingPermission
                                                                                                                      'Nothing)
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               TeamFeatureError
                                                                                                                             :> (CanThrowMany
                                                                                                                                   '[]
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("outlookCalIntegration"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                          OutlookCalIntegrationConfig)
                                                                                                                                                     :> Patch
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             OutlookCalIntegrationConfig)))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("iget",
                                                                                                     MlsE2EIdConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (Summary
                                                                                                          "Get config for mlsE2EId"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> ("teams"
                                                                                                                        :> (Capture
                                                                                                                              "tid"
                                                                                                                              TeamId
                                                                                                                            :> ("features"
                                                                                                                                :> ("mlsE2EId"
                                                                                                                                    :> Get
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            MlsE2EIdConfig))))))))))
                                                                                                 :<|> (Named
                                                                                                         '("iput",
                                                                                                           MlsE2EIdConfig)
                                                                                                         (Description
                                                                                                            ""
                                                                                                          :> (Summary
                                                                                                                "Put config for mlsE2EId"
                                                                                                              :> (CanThrow
                                                                                                                    ('MissingPermission
                                                                                                                       'Nothing)
                                                                                                                  :> (CanThrow
                                                                                                                        'NotATeamMember
                                                                                                                      :> (CanThrow
                                                                                                                            'TeamNotFound
                                                                                                                          :> (CanThrow
                                                                                                                                TeamFeatureError
                                                                                                                              :> (CanThrowMany
                                                                                                                                    '[]
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("mlsE2EId"
                                                                                                                                                  :> (ReqBody
                                                                                                                                                        '[JSON]
                                                                                                                                                        (Feature
                                                                                                                                                           MlsE2EIdConfig)
                                                                                                                                                      :> Put
                                                                                                                                                           '[JSON]
                                                                                                                                                           (LockableFeature
                                                                                                                                                              MlsE2EIdConfig)))))))))))))
                                                                                                       :<|> Named
                                                                                                              '("ipatch",
                                                                                                                MlsE2EIdConfig)
                                                                                                              (Description
                                                                                                                 ""
                                                                                                               :> (Summary
                                                                                                                     "Patch config for mlsE2EId"
                                                                                                                   :> (CanThrow
                                                                                                                         ('MissingPermission
                                                                                                                            'Nothing)
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     TeamFeatureError
                                                                                                                                   :> (CanThrowMany
                                                                                                                                         '[]
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("mlsE2EId"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                MlsE2EIdConfig)
                                                                                                                                                           :> Patch
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   MlsE2EIdConfig)))))))))))))))
                                                                                                :<|> ((Named
                                                                                                         '("iget",
                                                                                                           MlsMigrationConfig)
                                                                                                         (Description
                                                                                                            ""
                                                                                                          :> (Summary
                                                                                                                "Get config for mlsMigration"
                                                                                                              :> (CanThrow
                                                                                                                    ('MissingPermission
                                                                                                                       'Nothing)
                                                                                                                  :> (CanThrow
                                                                                                                        'NotATeamMember
                                                                                                                      :> (CanThrow
                                                                                                                            'TeamNotFound
                                                                                                                          :> ("teams"
                                                                                                                              :> (Capture
                                                                                                                                    "tid"
                                                                                                                                    TeamId
                                                                                                                                  :> ("features"
                                                                                                                                      :> ("mlsMigration"
                                                                                                                                          :> Get
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  MlsMigrationConfig))))))))))
                                                                                                       :<|> (Named
                                                                                                               '("iput",
                                                                                                                 MlsMigrationConfig)
                                                                                                               (Description
                                                                                                                  ""
                                                                                                                :> (Summary
                                                                                                                      "Put config for mlsMigration"
                                                                                                                    :> (CanThrow
                                                                                                                          ('MissingPermission
                                                                                                                             'Nothing)
                                                                                                                        :> (CanThrow
                                                                                                                              'NotATeamMember
                                                                                                                            :> (CanThrow
                                                                                                                                  'TeamNotFound
                                                                                                                                :> (CanThrow
                                                                                                                                      TeamFeatureError
                                                                                                                                    :> (CanThrowMany
                                                                                                                                          '[]
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("mlsMigration"
                                                                                                                                                        :> (ReqBody
                                                                                                                                                              '[JSON]
                                                                                                                                                              (Feature
                                                                                                                                                                 MlsMigrationConfig)
                                                                                                                                                            :> Put
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 (LockableFeature
                                                                                                                                                                    MlsMigrationConfig)))))))))))))
                                                                                                             :<|> Named
                                                                                                                    '("ipatch",
                                                                                                                      MlsMigrationConfig)
                                                                                                                    (Description
                                                                                                                       ""
                                                                                                                     :> (Summary
                                                                                                                           "Patch config for mlsMigration"
                                                                                                                         :> (CanThrow
                                                                                                                               ('MissingPermission
                                                                                                                                  'Nothing)
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotATeamMember
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TeamNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           TeamFeatureError
                                                                                                                                         :> (CanThrowMany
                                                                                                                                               '[]
                                                                                                                                             :> ("teams"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "tid"
                                                                                                                                                       TeamId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("mlsMigration"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                      MlsMigrationConfig)
                                                                                                                                                                 :> Patch
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         MlsMigrationConfig)))))))))))))))
                                                                                                      :<|> ((Named
                                                                                                               '("iget",
                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                               (Description
                                                                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                :> (Summary
                                                                                                                      "Get config for enforceFileDownloadLocation"
                                                                                                                    :> (CanThrow
                                                                                                                          ('MissingPermission
                                                                                                                             'Nothing)
                                                                                                                        :> (CanThrow
                                                                                                                              'NotATeamMember
                                                                                                                            :> (CanThrow
                                                                                                                                  'TeamNotFound
                                                                                                                                :> ("teams"
                                                                                                                                    :> (Capture
                                                                                                                                          "tid"
                                                                                                                                          TeamId
                                                                                                                                        :> ("features"
                                                                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                                                                :> Get
                                                                                                                                                     '[JSON]
                                                                                                                                                     (LockableFeature
                                                                                                                                                        EnforceFileDownloadLocationConfig))))))))))
                                                                                                             :<|> (Named
                                                                                                                     '("iput",
                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                     (Description
                                                                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                      :> (Summary
                                                                                                                            "Put config for enforceFileDownloadLocation"
                                                                                                                          :> (CanThrow
                                                                                                                                ('MissingPermission
                                                                                                                                   'Nothing)
                                                                                                                              :> (CanThrow
                                                                                                                                    'NotATeamMember
                                                                                                                                  :> (CanThrow
                                                                                                                                        'TeamNotFound
                                                                                                                                      :> (CanThrow
                                                                                                                                            TeamFeatureError
                                                                                                                                          :> (CanThrowMany
                                                                                                                                                '[]
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                                                                              :> (ReqBody
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (Feature
                                                                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                                                                  :> Put
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       (LockableFeature
                                                                                                                                                                          EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                   :<|> Named
                                                                                                                          '("ipatch",
                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                          (Description
                                                                                                                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                           :> (Summary
                                                                                                                                 "Patch config for enforceFileDownloadLocation"
                                                                                                                               :> (CanThrow
                                                                                                                                     ('MissingPermission
                                                                                                                                        'Nothing)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotATeamMember
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TeamNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 TeamFeatureError
                                                                                                                                               :> (CanThrowMany
                                                                                                                                                     '[]
                                                                                                                                                   :> ("teams"
                                                                                                                                                       :> (Capture
                                                                                                                                                             "tid"
                                                                                                                                                             TeamId
                                                                                                                                                           :> ("features"
                                                                                                                                                               :> ("enforceFileDownloadLocation"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeaturePatch
                                                                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                                                                       :> Patch
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("iget",
                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                    (Description
                                                                                                                       ""
                                                                                                                     :> (Summary
                                                                                                                           "Get config for limitedEventFanout"
                                                                                                                         :> (CanThrow
                                                                                                                               ('MissingPermission
                                                                                                                                  'Nothing)
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotATeamMember
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TeamNotFound
                                                                                                                                     :> ("teams"
                                                                                                                                         :> (Capture
                                                                                                                                               "tid"
                                                                                                                                               TeamId
                                                                                                                                             :> ("features"
                                                                                                                                                 :> ("limitedEventFanout"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             LimitedEventFanoutConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("iput",
                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                          (Description
                                                                                                                             ""
                                                                                                                           :> (Summary
                                                                                                                                 "Put config for limitedEventFanout"
                                                                                                                               :> (CanThrow
                                                                                                                                     ('MissingPermission
                                                                                                                                        'Nothing)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotATeamMember
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TeamNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 TeamFeatureError
                                                                                                                                               :> (CanThrowMany
                                                                                                                                                     '[]
                                                                                                                                                   :> ("teams"
                                                                                                                                                       :> (Capture
                                                                                                                                                             "tid"
                                                                                                                                                             TeamId
                                                                                                                                                           :> ("features"
                                                                                                                                                               :> ("limitedEventFanout"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (Feature
                                                                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                                                                       :> Put
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               LimitedEventFanoutConfig)))))))))))))
                                                                                                                        :<|> Named
                                                                                                                               '("ipatch",
                                                                                                                                 LimitedEventFanoutConfig)
                                                                                                                               (Description
                                                                                                                                  ""
                                                                                                                                :> (Summary
                                                                                                                                      "Patch config for limitedEventFanout"
                                                                                                                                    :> (CanThrow
                                                                                                                                          ('MissingPermission
                                                                                                                                             'Nothing)
                                                                                                                                        :> (CanThrow
                                                                                                                                              'NotATeamMember
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'TeamNotFound
                                                                                                                                                :> (CanThrow
                                                                                                                                                      TeamFeatureError
                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                          '[]
                                                                                                                                                        :> ("teams"
                                                                                                                                                            :> (Capture
                                                                                                                                                                  "tid"
                                                                                                                                                                  TeamId
                                                                                                                                                                :> ("features"
                                                                                                                                                                    :> ("limitedEventFanout"
                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeaturePatch
                                                                                                                                                                                 LimitedEventFanoutConfig)
                                                                                                                                                                            :> Patch
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                    LimitedEventFanoutConfig)))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", SearchVisibilityAvailableConfig)
     (Description ""
      :> (Summary "Get config for searchVisibility"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("searchVisibility"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature
                                              SearchVisibilityAvailableConfig))))))))))
   :<|> (Named
           '("iput", SearchVisibilityAvailableConfig)
           (Description ""
            :> (Summary "Put config for searchVisibility"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("searchVisibility"
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature SearchVisibilityAvailableConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                SearchVisibilityAvailableConfig)))))))))))))
         :<|> Named
                '("ipatch", SearchVisibilityAvailableConfig)
                (Description ""
                 :> (Summary "Patch config for searchVisibility"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("searchVisibility"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  SearchVisibilityAvailableConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SearchVisibilityAvailableConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", SearchVisibilityAvailableConfig)
     (Description (FeatureAPIDesc SearchVisibilityAvailableConfig)
      :> (Summary
            (AppendSymbol
               "Get config for " (FeatureSymbol SearchVisibilityAvailableConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol SearchVisibilityAvailableConfig
                                      :> Get
                                           '[JSON]
                                           (LockableFeature
                                              SearchVisibilityAvailableConfig))))))))))
   :<|> (Named
           '("iput", SearchVisibilityAvailableConfig)
           (Description (FeatureAPIDesc SearchVisibilityAvailableConfig)
            :> (Summary
                  (AppendSymbol
                     "Put config for " (FeatureSymbol SearchVisibilityAvailableConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors SearchVisibilityAvailableConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol SearchVisibilityAvailableConfig
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature SearchVisibilityAvailableConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                SearchVisibilityAvailableConfig)))))))))))))
         :<|> Named
                '("ipatch", SearchVisibilityAvailableConfig)
                (Description (FeatureAPIDesc SearchVisibilityAvailableConfig)
                 :> (Summary
                       (AppendSymbol
                          "Patch config for "
                          (FeatureSymbol SearchVisibilityAvailableConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany
                                           (FeatureErrors SearchVisibilityAvailableConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol
                                                           SearchVisibilityAvailableConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  SearchVisibilityAvailableConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SearchVisibilityAvailableConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", SearchVisibilityAvailableConfig)
     (Description ""
      :> (Summary "Get config for searchVisibility"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("searchVisibility"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature
                                              SearchVisibilityAvailableConfig))))))))))
   :<|> (Named
           '("iput", SearchVisibilityAvailableConfig)
           (Description ""
            :> (Summary "Put config for searchVisibility"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("searchVisibility"
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature SearchVisibilityAvailableConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                SearchVisibilityAvailableConfig)))))))))))))
         :<|> Named
                '("ipatch", SearchVisibilityAvailableConfig)
                (Description ""
                 :> (Summary "Patch config for searchVisibility"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("searchVisibility"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  SearchVisibilityAvailableConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SearchVisibilityAvailableConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", SearchVisibilityInboundConfig)
         (Description ""
          :> (Summary "Get config for searchVisibilityInbound"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("searchVisibilityInbound"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SearchVisibilityInboundConfig))))))))))
       :<|> (Named
               '("iput", SearchVisibilityInboundConfig)
               (Description ""
                :> (Summary "Put config for searchVisibilityInbound"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("searchVisibilityInbound"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature
                                                                 SearchVisibilityInboundConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SearchVisibilityInboundConfig)))))))))))))
             :<|> Named
                    '("ipatch", SearchVisibilityInboundConfig)
                    (Description ""
                     :> (Summary "Patch config for searchVisibilityInbound"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("searchVisibilityInbound"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      SearchVisibilityInboundConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SearchVisibilityInboundConfig)))))))))))))))
      :<|> ((Named
               '("iget", ValidateSAMLEmailsConfig)
               (Description ""
                :> (Summary "Get config for validateSAMLemails"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("validateSAMLemails"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        ValidateSAMLEmailsConfig))))))))))
             :<|> (Named
                     '("iput", ValidateSAMLEmailsConfig)
                     (Description ""
                      :> (Summary "Put config for validateSAMLemails"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("validateSAMLemails"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       ValidateSAMLEmailsConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          ValidateSAMLEmailsConfig)))))))))))))
                   :<|> Named
                          '("ipatch", ValidateSAMLEmailsConfig)
                          (Description ""
                           :> (Summary "Patch config for validateSAMLemails"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("validateSAMLemails"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            ValidateSAMLEmailsConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               ValidateSAMLEmailsConfig)))))))))))))))
            :<|> ((Named
                     '("iget", DigitalSignaturesConfig)
                     (Description ""
                      :> (Summary "Get config for digitalSignatures"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("digitalSignatures"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              DigitalSignaturesConfig))))))))))
                   :<|> (Named
                           '("iput", DigitalSignaturesConfig)
                           (Description ""
                            :> (Summary "Put config for digitalSignatures"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("digitalSignatures"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             DigitalSignaturesConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                DigitalSignaturesConfig)))))))))))))
                         :<|> Named
                                '("ipatch", DigitalSignaturesConfig)
                                (Description ""
                                 :> (Summary "Patch config for digitalSignatures"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("digitalSignatures"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  DigitalSignaturesConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     DigitalSignaturesConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", AppLockConfig)
                           (Description ""
                            :> (Summary "Get config for appLock"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("appLock"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    AppLockConfig))))))))))
                         :<|> (Named
                                 '("iput", AppLockConfig)
                                 (Description ""
                                  :> (Summary "Put config for appLock"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("appLock"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   AppLockConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      AppLockConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", AppLockConfig)
                                      (Description ""
                                       :> (Summary "Patch config for appLock"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("appLock"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        AppLockConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           AppLockConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", FileSharingConfig)
                                 (Description ""
                                  :> (Summary "Get config for fileSharing"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("fileSharing"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          FileSharingConfig))))))))))
                               :<|> (Named
                                       '("iput", FileSharingConfig)
                                       (Description ""
                                        :> (Summary "Put config for fileSharing"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("fileSharing"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         FileSharingConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            FileSharingConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", FileSharingConfig)
                                            (Description ""
                                             :> (Summary "Patch config for fileSharing"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("fileSharing"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              FileSharingConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 FileSharingConfig)))))))))))))))
                              :<|> (Named
                                      '("iget", ClassifiedDomainsConfig)
                                      (Description ""
                                       :> (Summary "Get config for classifiedDomains"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("classifiedDomains"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               ClassifiedDomainsConfig))))))))))
                                    :<|> ((Named
                                             '("iget", ConferenceCallingConfig)
                                             (Description ""
                                              :> (Summary "Get config for conferenceCalling"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("conferenceCalling"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      ConferenceCallingConfig))))))))))
                                           :<|> (Named
                                                   '("iput", ConferenceCallingConfig)
                                                   (Description ""
                                                    :> (Summary "Put config for conferenceCalling"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("conferenceCalling"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     ConferenceCallingConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        ConferenceCallingConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", ConferenceCallingConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Patch config for conferenceCalling"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("conferenceCalling"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          ConferenceCallingConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             ConferenceCallingConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", SelfDeletingMessagesConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Get config for selfDeletingMessages"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("selfDeletingMessages"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            SelfDeletingMessagesConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", SelfDeletingMessagesConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Put config for selfDeletingMessages"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("selfDeletingMessages"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           SelfDeletingMessagesConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              SelfDeletingMessagesConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch",
                                                                SelfDeletingMessagesConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for selfDeletingMessages"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("selfDeletingMessages"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                SelfDeletingMessagesConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   SelfDeletingMessagesConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget", GuestLinksConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Get config for conversationGuestLinks"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("conversationGuestLinks"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  GuestLinksConfig))))))))))
                                                       :<|> (Named
                                                               '("iput", GuestLinksConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for conversationGuestLinks"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("conversationGuestLinks"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 GuestLinksConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    GuestLinksConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch", GuestLinksConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for conversationGuestLinks"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("conversationGuestLinks"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      GuestLinksConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         GuestLinksConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget",
                                                                 SndFactorPasswordChallengeConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Get config for sndFactorPasswordChallenge"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("sndFactorPasswordChallenge"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        SndFactorPasswordChallengeConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput",
                                                                       SndFactorPasswordChallengeConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for sndFactorPasswordChallenge"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("sndFactorPasswordChallenge"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       SndFactorPasswordChallengeConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          SndFactorPasswordChallengeConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            SndFactorPasswordChallengeConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for sndFactorPasswordChallenge"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("sndFactorPasswordChallenge"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               SndFactorPasswordChallengeConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget", MLSConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Get config for mls"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("mls"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              MLSConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput", MLSConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Put config for mls"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mls"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             MLSConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                MLSConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  MLSConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Patch config for mls"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("mls"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  MLSConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     MLSConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("iget",
                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                            :> Get
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                         :<|> (Named
                                                                                 '("iput",
                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (Feature
                                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                               :<|> Named
                                                                                      '("ipatch",
                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeaturePatch
                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                   :> Patch
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("iget",
                                                                                   OutlookCalIntegrationConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Get config for outlookCalIntegration"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("outlookCalIntegration"
                                                                                                                  :> Get
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          OutlookCalIntegrationConfig))))))))))
                                                                               :<|> (Named
                                                                                       '("iput",
                                                                                         OutlookCalIntegrationConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Put config for outlookCalIntegration"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> (CanThrow
                                                                                                              TeamFeatureError
                                                                                                            :> (CanThrowMany
                                                                                                                  '[]
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("outlookCalIntegration"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      (Feature
                                                                                                                                         OutlookCalIntegrationConfig)
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            OutlookCalIntegrationConfig)))))))))))))
                                                                                     :<|> Named
                                                                                            '("ipatch",
                                                                                              OutlookCalIntegrationConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (Summary
                                                                                                   "Patch config for outlookCalIntegration"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   TeamFeatureError
                                                                                                                 :> (CanThrowMany
                                                                                                                       '[]
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("outlookCalIntegration"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeaturePatch
                                                                                                                                              OutlookCalIntegrationConfig)
                                                                                                                                         :> Patch
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 OutlookCalIntegrationConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("iget",
                                                                                         MlsE2EIdConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Get config for mlsE2EId"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("mlsE2EId"
                                                                                                                        :> Get
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                MlsE2EIdConfig))))))))))
                                                                                     :<|> (Named
                                                                                             '("iput",
                                                                                               MlsE2EIdConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Put config for mlsE2EId"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> (CanThrow
                                                                                                                    TeamFeatureError
                                                                                                                  :> (CanThrowMany
                                                                                                                        '[]
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("mlsE2EId"
                                                                                                                                      :> (ReqBody
                                                                                                                                            '[JSON]
                                                                                                                                            (Feature
                                                                                                                                               MlsE2EIdConfig)
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  MlsE2EIdConfig)))))))))))))
                                                                                           :<|> Named
                                                                                                  '("ipatch",
                                                                                                    MlsE2EIdConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (Summary
                                                                                                         "Patch config for mlsE2EId"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         TeamFeatureError
                                                                                                                       :> (CanThrowMany
                                                                                                                             '[]
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("mlsE2EId"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                    MlsE2EIdConfig)
                                                                                                                                               :> Patch
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       MlsE2EIdConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("iget",
                                                                                               MlsMigrationConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Get config for mlsMigration"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> ("teams"
                                                                                                                  :> (Capture
                                                                                                                        "tid"
                                                                                                                        TeamId
                                                                                                                      :> ("features"
                                                                                                                          :> ("mlsMigration"
                                                                                                                              :> Get
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      MlsMigrationConfig))))))))))
                                                                                           :<|> (Named
                                                                                                   '("iput",
                                                                                                     MlsMigrationConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (Summary
                                                                                                          "Put config for mlsMigration"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> (CanThrow
                                                                                                                          TeamFeatureError
                                                                                                                        :> (CanThrowMany
                                                                                                                              '[]
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("mlsMigration"
                                                                                                                                            :> (ReqBody
                                                                                                                                                  '[JSON]
                                                                                                                                                  (Feature
                                                                                                                                                     MlsMigrationConfig)
                                                                                                                                                :> Put
                                                                                                                                                     '[JSON]
                                                                                                                                                     (LockableFeature
                                                                                                                                                        MlsMigrationConfig)))))))))))))
                                                                                                 :<|> Named
                                                                                                        '("ipatch",
                                                                                                          MlsMigrationConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (Summary
                                                                                                               "Patch config for mlsMigration"
                                                                                                             :> (CanThrow
                                                                                                                   ('MissingPermission
                                                                                                                      'Nothing)
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               TeamFeatureError
                                                                                                                             :> (CanThrowMany
                                                                                                                                   '[]
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("mlsMigration"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                          MlsMigrationConfig)
                                                                                                                                                     :> Patch
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             MlsMigrationConfig)))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("iget",
                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                   (Description
                                                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                    :> (Summary
                                                                                                          "Get config for enforceFileDownloadLocation"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> ("teams"
                                                                                                                        :> (Capture
                                                                                                                              "tid"
                                                                                                                              TeamId
                                                                                                                            :> ("features"
                                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                                    :> Get
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            EnforceFileDownloadLocationConfig))))))))))
                                                                                                 :<|> (Named
                                                                                                         '("iput",
                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                         (Description
                                                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                          :> (Summary
                                                                                                                "Put config for enforceFileDownloadLocation"
                                                                                                              :> (CanThrow
                                                                                                                    ('MissingPermission
                                                                                                                       'Nothing)
                                                                                                                  :> (CanThrow
                                                                                                                        'NotATeamMember
                                                                                                                      :> (CanThrow
                                                                                                                            'TeamNotFound
                                                                                                                          :> (CanThrow
                                                                                                                                TeamFeatureError
                                                                                                                              :> (CanThrowMany
                                                                                                                                    '[]
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                                                                  :> (ReqBody
                                                                                                                                                        '[JSON]
                                                                                                                                                        (Feature
                                                                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                                                                      :> Put
                                                                                                                                                           '[JSON]
                                                                                                                                                           (LockableFeature
                                                                                                                                                              EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                       :<|> Named
                                                                                                              '("ipatch",
                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                              (Description
                                                                                                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                               :> (Summary
                                                                                                                     "Patch config for enforceFileDownloadLocation"
                                                                                                                   :> (CanThrow
                                                                                                                         ('MissingPermission
                                                                                                                            'Nothing)
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     TeamFeatureError
                                                                                                                                   :> (CanThrowMany
                                                                                                                                         '[]
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("enforceFileDownloadLocation"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                                                           :> Patch
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                :<|> (Named
                                                                                                        '("iget",
                                                                                                          LimitedEventFanoutConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (Summary
                                                                                                               "Get config for limitedEventFanout"
                                                                                                             :> (CanThrow
                                                                                                                   ('MissingPermission
                                                                                                                      'Nothing)
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> ("teams"
                                                                                                                             :> (Capture
                                                                                                                                   "tid"
                                                                                                                                   TeamId
                                                                                                                                 :> ("features"
                                                                                                                                     :> ("limitedEventFanout"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 LimitedEventFanoutConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("iput",
                                                                                                                LimitedEventFanoutConfig)
                                                                                                              (Description
                                                                                                                 ""
                                                                                                               :> (Summary
                                                                                                                     "Put config for limitedEventFanout"
                                                                                                                   :> (CanThrow
                                                                                                                         ('MissingPermission
                                                                                                                            'Nothing)
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     TeamFeatureError
                                                                                                                                   :> (CanThrowMany
                                                                                                                                         '[]
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("limitedEventFanout"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             (Feature
                                                                                                                                                                LimitedEventFanoutConfig)
                                                                                                                                                           :> Put
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   LimitedEventFanoutConfig)))))))))))))
                                                                                                            :<|> Named
                                                                                                                   '("ipatch",
                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                   (Description
                                                                                                                      ""
                                                                                                                    :> (Summary
                                                                                                                          "Patch config for limitedEventFanout"
                                                                                                                        :> (CanThrow
                                                                                                                              ('MissingPermission
                                                                                                                                 'Nothing)
                                                                                                                            :> (CanThrow
                                                                                                                                  'NotATeamMember
                                                                                                                                :> (CanThrow
                                                                                                                                      'TeamNotFound
                                                                                                                                    :> (CanThrow
                                                                                                                                          TeamFeatureError
                                                                                                                                        :> (CanThrowMany
                                                                                                                                              '[]
                                                                                                                                            :> ("teams"
                                                                                                                                                :> (Capture
                                                                                                                                                      "tid"
                                                                                                                                                      TeamId
                                                                                                                                                    :> ("features"
                                                                                                                                                        :> ("limitedEventFanout"
                                                                                                                                                            :> (ReqBody
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeaturePatch
                                                                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                                                                :> Patch
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeature
                                                                                                                                                                        LimitedEventFanoutConfig)))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", SearchVisibilityAvailableConfig)
         (Description ""
          :> (Summary "Get config for searchVisibility"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("searchVisibility"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SearchVisibilityAvailableConfig))))))))))
       :<|> (Named
               '("iput", SearchVisibilityAvailableConfig)
               (Description ""
                :> (Summary "Put config for searchVisibility"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("searchVisibility"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature
                                                                 SearchVisibilityAvailableConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SearchVisibilityAvailableConfig)))))))))))))
             :<|> Named
                    '("ipatch", SearchVisibilityAvailableConfig)
                    (Description ""
                     :> (Summary "Patch config for searchVisibility"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("searchVisibility"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      SearchVisibilityAvailableConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SearchVisibilityAvailableConfig)))))))))))))))
      :<|> ((Named
               '("iget", SearchVisibilityInboundConfig)
               (Description ""
                :> (Summary "Get config for searchVisibilityInbound"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("searchVisibilityInbound"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        SearchVisibilityInboundConfig))))))))))
             :<|> (Named
                     '("iput", SearchVisibilityInboundConfig)
                     (Description ""
                      :> (Summary "Put config for searchVisibilityInbound"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("searchVisibilityInbound"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       SearchVisibilityInboundConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          SearchVisibilityInboundConfig)))))))))))))
                   :<|> Named
                          '("ipatch", SearchVisibilityInboundConfig)
                          (Description ""
                           :> (Summary "Patch config for searchVisibilityInbound"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("searchVisibilityInbound"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            SearchVisibilityInboundConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SearchVisibilityInboundConfig)))))))))))))))
            :<|> ((Named
                     '("iget", ValidateSAMLEmailsConfig)
                     (Description ""
                      :> (Summary "Get config for validateSAMLemails"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("validateSAMLemails"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              ValidateSAMLEmailsConfig))))))))))
                   :<|> (Named
                           '("iput", ValidateSAMLEmailsConfig)
                           (Description ""
                            :> (Summary "Put config for validateSAMLemails"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("validateSAMLemails"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             ValidateSAMLEmailsConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                ValidateSAMLEmailsConfig)))))))))))))
                         :<|> Named
                                '("ipatch", ValidateSAMLEmailsConfig)
                                (Description ""
                                 :> (Summary "Patch config for validateSAMLemails"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("validateSAMLemails"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  ValidateSAMLEmailsConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     ValidateSAMLEmailsConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", DigitalSignaturesConfig)
                           (Description ""
                            :> (Summary "Get config for digitalSignatures"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("digitalSignatures"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    DigitalSignaturesConfig))))))))))
                         :<|> (Named
                                 '("iput", DigitalSignaturesConfig)
                                 (Description ""
                                  :> (Summary "Put config for digitalSignatures"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("digitalSignatures"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   DigitalSignaturesConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      DigitalSignaturesConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", DigitalSignaturesConfig)
                                      (Description ""
                                       :> (Summary "Patch config for digitalSignatures"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("digitalSignatures"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        DigitalSignaturesConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           DigitalSignaturesConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", AppLockConfig)
                                 (Description ""
                                  :> (Summary "Get config for appLock"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("appLock"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          AppLockConfig))))))))))
                               :<|> (Named
                                       '("iput", AppLockConfig)
                                       (Description ""
                                        :> (Summary "Put config for appLock"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("appLock"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         AppLockConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            AppLockConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", AppLockConfig)
                                            (Description ""
                                             :> (Summary "Patch config for appLock"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("appLock"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              AppLockConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 AppLockConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", FileSharingConfig)
                                       (Description ""
                                        :> (Summary "Get config for fileSharing"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("fileSharing"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                FileSharingConfig))))))))))
                                     :<|> (Named
                                             '("iput", FileSharingConfig)
                                             (Description ""
                                              :> (Summary "Put config for fileSharing"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("fileSharing"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               FileSharingConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  FileSharingConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", FileSharingConfig)
                                                  (Description ""
                                                   :> (Summary "Patch config for fileSharing"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("fileSharing"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    FileSharingConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       FileSharingConfig)))))))))))))))
                                    :<|> (Named
                                            '("iget", ClassifiedDomainsConfig)
                                            (Description ""
                                             :> (Summary "Get config for classifiedDomains"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("classifiedDomains"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     ClassifiedDomainsConfig))))))))))
                                          :<|> ((Named
                                                   '("iget", ConferenceCallingConfig)
                                                   (Description ""
                                                    :> (Summary "Get config for conferenceCalling"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("conferenceCalling"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            ConferenceCallingConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", ConferenceCallingConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Put config for conferenceCalling"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("conferenceCalling"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           ConferenceCallingConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              ConferenceCallingConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch", ConferenceCallingConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for conferenceCalling"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("conferenceCalling"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                ConferenceCallingConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   ConferenceCallingConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget", SelfDeletingMessagesConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Get config for selfDeletingMessages"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("selfDeletingMessages"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  SelfDeletingMessagesConfig))))))))))
                                                       :<|> (Named
                                                               '("iput", SelfDeletingMessagesConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for selfDeletingMessages"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("selfDeletingMessages"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 SelfDeletingMessagesConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    SelfDeletingMessagesConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch",
                                                                      SelfDeletingMessagesConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for selfDeletingMessages"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("selfDeletingMessages"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      SelfDeletingMessagesConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         SelfDeletingMessagesConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget", GuestLinksConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Get config for conversationGuestLinks"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("conversationGuestLinks"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        GuestLinksConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput", GuestLinksConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for conversationGuestLinks"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("conversationGuestLinks"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       GuestLinksConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          GuestLinksConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            GuestLinksConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for conversationGuestLinks"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("conversationGuestLinks"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            GuestLinksConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               GuestLinksConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget",
                                                                       SndFactorPasswordChallengeConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Get config for sndFactorPasswordChallenge"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("sndFactorPasswordChallenge"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              SndFactorPasswordChallengeConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput",
                                                                             SndFactorPasswordChallengeConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Put config for sndFactorPasswordChallenge"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("sndFactorPasswordChallenge"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             SndFactorPasswordChallengeConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                SndFactorPasswordChallengeConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  SndFactorPasswordChallengeConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Patch config for sndFactorPasswordChallenge"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("sndFactorPasswordChallenge"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     SndFactorPasswordChallengeConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("iget", MLSConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Get config for mls"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("mls"
                                                                                                            :> Get
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    MLSConfig))))))))))
                                                                         :<|> (Named
                                                                                 '("iput",
                                                                                   MLSConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Put config for mls"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mls"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (Feature
                                                                                                                                   MLSConfig)
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      MLSConfig)))))))))))))
                                                                               :<|> Named
                                                                                      '("ipatch",
                                                                                        MLSConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Patch config for mls"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("mls"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeaturePatch
                                                                                                                                        MLSConfig)
                                                                                                                                   :> Patch
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           MLSConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("iget",
                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                  :> Get
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                               :<|> (Named
                                                                                       '("iput",
                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> (CanThrow
                                                                                                              TeamFeatureError
                                                                                                            :> (CanThrowMany
                                                                                                                  '[]
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      (Feature
                                                                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                     :<|> Named
                                                                                            '("ipatch",
                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (Summary
                                                                                                   "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   TeamFeatureError
                                                                                                                 :> (CanThrowMany
                                                                                                                       '[]
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeaturePatch
                                                                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                         :> Patch
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("iget",
                                                                                         OutlookCalIntegrationConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Get config for outlookCalIntegration"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("outlookCalIntegration"
                                                                                                                        :> Get
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                OutlookCalIntegrationConfig))))))))))
                                                                                     :<|> (Named
                                                                                             '("iput",
                                                                                               OutlookCalIntegrationConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Put config for outlookCalIntegration"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> (CanThrow
                                                                                                                    TeamFeatureError
                                                                                                                  :> (CanThrowMany
                                                                                                                        '[]
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("outlookCalIntegration"
                                                                                                                                      :> (ReqBody
                                                                                                                                            '[JSON]
                                                                                                                                            (Feature
                                                                                                                                               OutlookCalIntegrationConfig)
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  OutlookCalIntegrationConfig)))))))))))))
                                                                                           :<|> Named
                                                                                                  '("ipatch",
                                                                                                    OutlookCalIntegrationConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (Summary
                                                                                                         "Patch config for outlookCalIntegration"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         TeamFeatureError
                                                                                                                       :> (CanThrowMany
                                                                                                                             '[]
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("outlookCalIntegration"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                    OutlookCalIntegrationConfig)
                                                                                                                                               :> Patch
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       OutlookCalIntegrationConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("iget",
                                                                                               MlsE2EIdConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Get config for mlsE2EId"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> ("teams"
                                                                                                                  :> (Capture
                                                                                                                        "tid"
                                                                                                                        TeamId
                                                                                                                      :> ("features"
                                                                                                                          :> ("mlsE2EId"
                                                                                                                              :> Get
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      MlsE2EIdConfig))))))))))
                                                                                           :<|> (Named
                                                                                                   '("iput",
                                                                                                     MlsE2EIdConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (Summary
                                                                                                          "Put config for mlsE2EId"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> (CanThrow
                                                                                                                          TeamFeatureError
                                                                                                                        :> (CanThrowMany
                                                                                                                              '[]
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("mlsE2EId"
                                                                                                                                            :> (ReqBody
                                                                                                                                                  '[JSON]
                                                                                                                                                  (Feature
                                                                                                                                                     MlsE2EIdConfig)
                                                                                                                                                :> Put
                                                                                                                                                     '[JSON]
                                                                                                                                                     (LockableFeature
                                                                                                                                                        MlsE2EIdConfig)))))))))))))
                                                                                                 :<|> Named
                                                                                                        '("ipatch",
                                                                                                          MlsE2EIdConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (Summary
                                                                                                               "Patch config for mlsE2EId"
                                                                                                             :> (CanThrow
                                                                                                                   ('MissingPermission
                                                                                                                      'Nothing)
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               TeamFeatureError
                                                                                                                             :> (CanThrowMany
                                                                                                                                   '[]
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("mlsE2EId"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                          MlsE2EIdConfig)
                                                                                                                                                     :> Patch
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             MlsE2EIdConfig)))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("iget",
                                                                                                     MlsMigrationConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (Summary
                                                                                                          "Get config for mlsMigration"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> ("teams"
                                                                                                                        :> (Capture
                                                                                                                              "tid"
                                                                                                                              TeamId
                                                                                                                            :> ("features"
                                                                                                                                :> ("mlsMigration"
                                                                                                                                    :> Get
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            MlsMigrationConfig))))))))))
                                                                                                 :<|> (Named
                                                                                                         '("iput",
                                                                                                           MlsMigrationConfig)
                                                                                                         (Description
                                                                                                            ""
                                                                                                          :> (Summary
                                                                                                                "Put config for mlsMigration"
                                                                                                              :> (CanThrow
                                                                                                                    ('MissingPermission
                                                                                                                       'Nothing)
                                                                                                                  :> (CanThrow
                                                                                                                        'NotATeamMember
                                                                                                                      :> (CanThrow
                                                                                                                            'TeamNotFound
                                                                                                                          :> (CanThrow
                                                                                                                                TeamFeatureError
                                                                                                                              :> (CanThrowMany
                                                                                                                                    '[]
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("mlsMigration"
                                                                                                                                                  :> (ReqBody
                                                                                                                                                        '[JSON]
                                                                                                                                                        (Feature
                                                                                                                                                           MlsMigrationConfig)
                                                                                                                                                      :> Put
                                                                                                                                                           '[JSON]
                                                                                                                                                           (LockableFeature
                                                                                                                                                              MlsMigrationConfig)))))))))))))
                                                                                                       :<|> Named
                                                                                                              '("ipatch",
                                                                                                                MlsMigrationConfig)
                                                                                                              (Description
                                                                                                                 ""
                                                                                                               :> (Summary
                                                                                                                     "Patch config for mlsMigration"
                                                                                                                   :> (CanThrow
                                                                                                                         ('MissingPermission
                                                                                                                            'Nothing)
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     TeamFeatureError
                                                                                                                                   :> (CanThrowMany
                                                                                                                                         '[]
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("mlsMigration"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                MlsMigrationConfig)
                                                                                                                                                           :> Patch
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   MlsMigrationConfig)))))))))))))))
                                                                                                :<|> ((Named
                                                                                                         '("iget",
                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                         (Description
                                                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                          :> (Summary
                                                                                                                "Get config for enforceFileDownloadLocation"
                                                                                                              :> (CanThrow
                                                                                                                    ('MissingPermission
                                                                                                                       'Nothing)
                                                                                                                  :> (CanThrow
                                                                                                                        'NotATeamMember
                                                                                                                      :> (CanThrow
                                                                                                                            'TeamNotFound
                                                                                                                          :> ("teams"
                                                                                                                              :> (Capture
                                                                                                                                    "tid"
                                                                                                                                    TeamId
                                                                                                                                  :> ("features"
                                                                                                                                      :> ("enforceFileDownloadLocation"
                                                                                                                                          :> Get
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  EnforceFileDownloadLocationConfig))))))))))
                                                                                                       :<|> (Named
                                                                                                               '("iput",
                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                               (Description
                                                                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                :> (Summary
                                                                                                                      "Put config for enforceFileDownloadLocation"
                                                                                                                    :> (CanThrow
                                                                                                                          ('MissingPermission
                                                                                                                             'Nothing)
                                                                                                                        :> (CanThrow
                                                                                                                              'NotATeamMember
                                                                                                                            :> (CanThrow
                                                                                                                                  'TeamNotFound
                                                                                                                                :> (CanThrow
                                                                                                                                      TeamFeatureError
                                                                                                                                    :> (CanThrowMany
                                                                                                                                          '[]
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                                                                        :> (ReqBody
                                                                                                                                                              '[JSON]
                                                                                                                                                              (Feature
                                                                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                                                                            :> Put
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 (LockableFeature
                                                                                                                                                                    EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                             :<|> Named
                                                                                                                    '("ipatch",
                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                    (Description
                                                                                                                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                     :> (Summary
                                                                                                                           "Patch config for enforceFileDownloadLocation"
                                                                                                                         :> (CanThrow
                                                                                                                               ('MissingPermission
                                                                                                                                  'Nothing)
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotATeamMember
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TeamNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           TeamFeatureError
                                                                                                                                         :> (CanThrowMany
                                                                                                                                               '[]
                                                                                                                                             :> ("teams"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "tid"
                                                                                                                                                       TeamId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("enforceFileDownloadLocation"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeaturePatch
                                                                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                                                                 :> Patch
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("iget",
                                                                                                                LimitedEventFanoutConfig)
                                                                                                              (Description
                                                                                                                 ""
                                                                                                               :> (Summary
                                                                                                                     "Get config for limitedEventFanout"
                                                                                                                   :> (CanThrow
                                                                                                                         ('MissingPermission
                                                                                                                            'Nothing)
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> ("teams"
                                                                                                                                   :> (Capture
                                                                                                                                         "tid"
                                                                                                                                         TeamId
                                                                                                                                       :> ("features"
                                                                                                                                           :> ("limitedEventFanout"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       LimitedEventFanoutConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("iput",
                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                    (Description
                                                                                                                       ""
                                                                                                                     :> (Summary
                                                                                                                           "Put config for limitedEventFanout"
                                                                                                                         :> (CanThrow
                                                                                                                               ('MissingPermission
                                                                                                                                  'Nothing)
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotATeamMember
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TeamNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           TeamFeatureError
                                                                                                                                         :> (CanThrowMany
                                                                                                                                               '[]
                                                                                                                                             :> ("teams"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "tid"
                                                                                                                                                       TeamId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("limitedEventFanout"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (Feature
                                                                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                                                                 :> Put
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         LimitedEventFanoutConfig)))))))))))))
                                                                                                                  :<|> Named
                                                                                                                         '("ipatch",
                                                                                                                           LimitedEventFanoutConfig)
                                                                                                                         (Description
                                                                                                                            ""
                                                                                                                          :> (Summary
                                                                                                                                "Patch config for limitedEventFanout"
                                                                                                                              :> (CanThrow
                                                                                                                                    ('MissingPermission
                                                                                                                                       'Nothing)
                                                                                                                                  :> (CanThrow
                                                                                                                                        'NotATeamMember
                                                                                                                                      :> (CanThrow
                                                                                                                                            'TeamNotFound
                                                                                                                                          :> (CanThrow
                                                                                                                                                TeamFeatureError
                                                                                                                                              :> (CanThrowMany
                                                                                                                                                    '[]
                                                                                                                                                  :> ("teams"
                                                                                                                                                      :> (Capture
                                                                                                                                                            "tid"
                                                                                                                                                            TeamId
                                                                                                                                                          :> ("features"
                                                                                                                                                              :> ("limitedEventFanout"
                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeaturePatch
                                                                                                                                                                           LimitedEventFanoutConfig)
                                                                                                                                                                      :> Patch
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeature
                                                                                                                                                                              LimitedEventFanoutConfig))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", SearchVisibilityInboundConfig)
     (Description ""
      :> (Summary "Get config for searchVisibilityInbound"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("searchVisibilityInbound"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature SearchVisibilityInboundConfig))))))))))
   :<|> (Named
           '("iput", SearchVisibilityInboundConfig)
           (Description ""
            :> (Summary "Put config for searchVisibilityInbound"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("searchVisibilityInbound"
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature SearchVisibilityInboundConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                SearchVisibilityInboundConfig)))))))))))))
         :<|> Named
                '("ipatch", SearchVisibilityInboundConfig)
                (Description ""
                 :> (Summary "Patch config for searchVisibilityInbound"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("searchVisibilityInbound"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  SearchVisibilityInboundConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SearchVisibilityInboundConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", SearchVisibilityInboundConfig)
     (Description (FeatureAPIDesc SearchVisibilityInboundConfig)
      :> (Summary
            (AppendSymbol
               "Get config for " (FeatureSymbol SearchVisibilityInboundConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol SearchVisibilityInboundConfig
                                      :> Get
                                           '[JSON]
                                           (LockableFeature SearchVisibilityInboundConfig))))))))))
   :<|> (Named
           '("iput", SearchVisibilityInboundConfig)
           (Description (FeatureAPIDesc SearchVisibilityInboundConfig)
            :> (Summary
                  (AppendSymbol
                     "Put config for " (FeatureSymbol SearchVisibilityInboundConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors SearchVisibilityInboundConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol SearchVisibilityInboundConfig
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature SearchVisibilityInboundConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                SearchVisibilityInboundConfig)))))))))))))
         :<|> Named
                '("ipatch", SearchVisibilityInboundConfig)
                (Description (FeatureAPIDesc SearchVisibilityInboundConfig)
                 :> (Summary
                       (AppendSymbol
                          "Patch config for " (FeatureSymbol SearchVisibilityInboundConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany (FeatureErrors SearchVisibilityInboundConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol SearchVisibilityInboundConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  SearchVisibilityInboundConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SearchVisibilityInboundConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", SearchVisibilityInboundConfig)
     (Description ""
      :> (Summary "Get config for searchVisibilityInbound"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("searchVisibilityInbound"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature SearchVisibilityInboundConfig))))))))))
   :<|> (Named
           '("iput", SearchVisibilityInboundConfig)
           (Description ""
            :> (Summary "Put config for searchVisibilityInbound"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("searchVisibilityInbound"
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature SearchVisibilityInboundConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                SearchVisibilityInboundConfig)))))))))))))
         :<|> Named
                '("ipatch", SearchVisibilityInboundConfig)
                (Description ""
                 :> (Summary "Patch config for searchVisibilityInbound"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("searchVisibilityInbound"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  SearchVisibilityInboundConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SearchVisibilityInboundConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", ValidateSAMLEmailsConfig)
         (Description ""
          :> (Summary "Get config for validateSAMLemails"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("validateSAMLemails"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature ValidateSAMLEmailsConfig))))))))))
       :<|> (Named
               '("iput", ValidateSAMLEmailsConfig)
               (Description ""
                :> (Summary "Put config for validateSAMLemails"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("validateSAMLemails"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature ValidateSAMLEmailsConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    ValidateSAMLEmailsConfig)))))))))))))
             :<|> Named
                    '("ipatch", ValidateSAMLEmailsConfig)
                    (Description ""
                     :> (Summary "Patch config for validateSAMLemails"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("validateSAMLemails"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      ValidateSAMLEmailsConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         ValidateSAMLEmailsConfig)))))))))))))))
      :<|> ((Named
               '("iget", DigitalSignaturesConfig)
               (Description ""
                :> (Summary "Get config for digitalSignatures"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("digitalSignatures"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        DigitalSignaturesConfig))))))))))
             :<|> (Named
                     '("iput", DigitalSignaturesConfig)
                     (Description ""
                      :> (Summary "Put config for digitalSignatures"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("digitalSignatures"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       DigitalSignaturesConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          DigitalSignaturesConfig)))))))))))))
                   :<|> Named
                          '("ipatch", DigitalSignaturesConfig)
                          (Description ""
                           :> (Summary "Patch config for digitalSignatures"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("digitalSignatures"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            DigitalSignaturesConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               DigitalSignaturesConfig)))))))))))))))
            :<|> ((Named
                     '("iget", AppLockConfig)
                     (Description ""
                      :> (Summary "Get config for appLock"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("appLock"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature AppLockConfig))))))))))
                   :<|> (Named
                           '("iput", AppLockConfig)
                           (Description ""
                            :> (Summary "Put config for appLock"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("appLock"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature AppLockConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                AppLockConfig)))))))))))))
                         :<|> Named
                                '("ipatch", AppLockConfig)
                                (Description ""
                                 :> (Summary "Patch config for appLock"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("appLock"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  AppLockConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     AppLockConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", FileSharingConfig)
                           (Description ""
                            :> (Summary "Get config for fileSharing"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("fileSharing"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    FileSharingConfig))))))))))
                         :<|> (Named
                                 '("iput", FileSharingConfig)
                                 (Description ""
                                  :> (Summary "Put config for fileSharing"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("fileSharing"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   FileSharingConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      FileSharingConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", FileSharingConfig)
                                      (Description ""
                                       :> (Summary "Patch config for fileSharing"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("fileSharing"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        FileSharingConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           FileSharingConfig)))))))))))))))
                        :<|> (Named
                                '("iget", ClassifiedDomainsConfig)
                                (Description ""
                                 :> (Summary "Get config for classifiedDomains"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("classifiedDomains"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         ClassifiedDomainsConfig))))))))))
                              :<|> ((Named
                                       '("iget", ConferenceCallingConfig)
                                       (Description ""
                                        :> (Summary "Get config for conferenceCalling"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("conferenceCalling"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                ConferenceCallingConfig))))))))))
                                     :<|> (Named
                                             '("iput", ConferenceCallingConfig)
                                             (Description ""
                                              :> (Summary "Put config for conferenceCalling"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("conferenceCalling"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               ConferenceCallingConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  ConferenceCallingConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", ConferenceCallingConfig)
                                                  (Description ""
                                                   :> (Summary "Patch config for conferenceCalling"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("conferenceCalling"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    ConferenceCallingConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       ConferenceCallingConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", SelfDeletingMessagesConfig)
                                             (Description ""
                                              :> (Summary "Get config for selfDeletingMessages"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("selfDeletingMessages"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      SelfDeletingMessagesConfig))))))))))
                                           :<|> (Named
                                                   '("iput", SelfDeletingMessagesConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Put config for selfDeletingMessages"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("selfDeletingMessages"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     SelfDeletingMessagesConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        SelfDeletingMessagesConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", SelfDeletingMessagesConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Patch config for selfDeletingMessages"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("selfDeletingMessages"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          SelfDeletingMessagesConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             SelfDeletingMessagesConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", GuestLinksConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Get config for conversationGuestLinks"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("conversationGuestLinks"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            GuestLinksConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", GuestLinksConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Put config for conversationGuestLinks"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("conversationGuestLinks"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           GuestLinksConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              GuestLinksConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch", GuestLinksConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for conversationGuestLinks"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("conversationGuestLinks"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                GuestLinksConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   GuestLinksConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget", SndFactorPasswordChallengeConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Get config for sndFactorPasswordChallenge"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("sndFactorPasswordChallenge"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  SndFactorPasswordChallengeConfig))))))))))
                                                       :<|> (Named
                                                               '("iput",
                                                                 SndFactorPasswordChallengeConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for sndFactorPasswordChallenge"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("sndFactorPasswordChallenge"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 SndFactorPasswordChallengeConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    SndFactorPasswordChallengeConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch",
                                                                      SndFactorPasswordChallengeConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for sndFactorPasswordChallenge"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         SndFactorPasswordChallengeConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget", MLSConfig)
                                                               (Description ""
                                                                :> (Summary "Get config for mls"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("mls"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        MLSConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput", MLSConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for mls"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mls"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       MLSConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          MLSConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch", MLSConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for mls"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("mls"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            MLSConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               MLSConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget",
                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Get config for exposeInvitationURLsToTeamAdmin"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput",
                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("iget",
                                                                             OutlookCalIntegrationConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Get config for outlookCalIntegration"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("outlookCalIntegration"
                                                                                                            :> Get
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    OutlookCalIntegrationConfig))))))))))
                                                                         :<|> (Named
                                                                                 '("iput",
                                                                                   OutlookCalIntegrationConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Put config for outlookCalIntegration"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("outlookCalIntegration"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (Feature
                                                                                                                                   OutlookCalIntegrationConfig)
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      OutlookCalIntegrationConfig)))))))))))))
                                                                               :<|> Named
                                                                                      '("ipatch",
                                                                                        OutlookCalIntegrationConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Patch config for outlookCalIntegration"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("outlookCalIntegration"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeaturePatch
                                                                                                                                        OutlookCalIntegrationConfig)
                                                                                                                                   :> Patch
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           OutlookCalIntegrationConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("iget",
                                                                                   MlsE2EIdConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Get config for mlsE2EId"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("mlsE2EId"
                                                                                                                  :> Get
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          MlsE2EIdConfig))))))))))
                                                                               :<|> (Named
                                                                                       '("iput",
                                                                                         MlsE2EIdConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Put config for mlsE2EId"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> (CanThrow
                                                                                                              TeamFeatureError
                                                                                                            :> (CanThrowMany
                                                                                                                  '[]
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mlsE2EId"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      (Feature
                                                                                                                                         MlsE2EIdConfig)
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            MlsE2EIdConfig)))))))))))))
                                                                                     :<|> Named
                                                                                            '("ipatch",
                                                                                              MlsE2EIdConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (Summary
                                                                                                   "Patch config for mlsE2EId"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   TeamFeatureError
                                                                                                                 :> (CanThrowMany
                                                                                                                       '[]
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("mlsE2EId"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeaturePatch
                                                                                                                                              MlsE2EIdConfig)
                                                                                                                                         :> Patch
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 MlsE2EIdConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("iget",
                                                                                         MlsMigrationConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Get config for mlsMigration"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("mlsMigration"
                                                                                                                        :> Get
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                MlsMigrationConfig))))))))))
                                                                                     :<|> (Named
                                                                                             '("iput",
                                                                                               MlsMigrationConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Put config for mlsMigration"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> (CanThrow
                                                                                                                    TeamFeatureError
                                                                                                                  :> (CanThrowMany
                                                                                                                        '[]
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("mlsMigration"
                                                                                                                                      :> (ReqBody
                                                                                                                                            '[JSON]
                                                                                                                                            (Feature
                                                                                                                                               MlsMigrationConfig)
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  MlsMigrationConfig)))))))))))))
                                                                                           :<|> Named
                                                                                                  '("ipatch",
                                                                                                    MlsMigrationConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (Summary
                                                                                                         "Patch config for mlsMigration"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         TeamFeatureError
                                                                                                                       :> (CanThrowMany
                                                                                                                             '[]
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("mlsMigration"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                    MlsMigrationConfig)
                                                                                                                                               :> Patch
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       MlsMigrationConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("iget",
                                                                                               EnforceFileDownloadLocationConfig)
                                                                                             (Description
                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                              :> (Summary
                                                                                                    "Get config for enforceFileDownloadLocation"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> ("teams"
                                                                                                                  :> (Capture
                                                                                                                        "tid"
                                                                                                                        TeamId
                                                                                                                      :> ("features"
                                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                                              :> Get
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      EnforceFileDownloadLocationConfig))))))))))
                                                                                           :<|> (Named
                                                                                                   '("iput",
                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                   (Description
                                                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                    :> (Summary
                                                                                                          "Put config for enforceFileDownloadLocation"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> (CanThrow
                                                                                                                          TeamFeatureError
                                                                                                                        :> (CanThrowMany
                                                                                                                              '[]
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("enforceFileDownloadLocation"
                                                                                                                                            :> (ReqBody
                                                                                                                                                  '[JSON]
                                                                                                                                                  (Feature
                                                                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                                                                :> Put
                                                                                                                                                     '[JSON]
                                                                                                                                                     (LockableFeature
                                                                                                                                                        EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                 :<|> Named
                                                                                                        '("ipatch",
                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                        (Description
                                                                                                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                         :> (Summary
                                                                                                               "Patch config for enforceFileDownloadLocation"
                                                                                                             :> (CanThrow
                                                                                                                   ('MissingPermission
                                                                                                                      'Nothing)
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               TeamFeatureError
                                                                                                                             :> (CanThrowMany
                                                                                                                                   '[]
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("enforceFileDownloadLocation"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                                                     :> Patch
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                          :<|> (Named
                                                                                                  '("iget",
                                                                                                    LimitedEventFanoutConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (Summary
                                                                                                         "Get config for limitedEventFanout"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> ("teams"
                                                                                                                       :> (Capture
                                                                                                                             "tid"
                                                                                                                             TeamId
                                                                                                                           :> ("features"
                                                                                                                               :> ("limitedEventFanout"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           LimitedEventFanoutConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("iput",
                                                                                                          LimitedEventFanoutConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (Summary
                                                                                                               "Put config for limitedEventFanout"
                                                                                                             :> (CanThrow
                                                                                                                   ('MissingPermission
                                                                                                                      'Nothing)
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               TeamFeatureError
                                                                                                                             :> (CanThrowMany
                                                                                                                                   '[]
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("limitedEventFanout"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       (Feature
                                                                                                                                                          LimitedEventFanoutConfig)
                                                                                                                                                     :> Put
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             LimitedEventFanoutConfig)))))))))))))
                                                                                                      :<|> Named
                                                                                                             '("ipatch",
                                                                                                               LimitedEventFanoutConfig)
                                                                                                             (Description
                                                                                                                ""
                                                                                                              :> (Summary
                                                                                                                    "Patch config for limitedEventFanout"
                                                                                                                  :> (CanThrow
                                                                                                                        ('MissingPermission
                                                                                                                           'Nothing)
                                                                                                                      :> (CanThrow
                                                                                                                            'NotATeamMember
                                                                                                                          :> (CanThrow
                                                                                                                                'TeamNotFound
                                                                                                                              :> (CanThrow
                                                                                                                                    TeamFeatureError
                                                                                                                                  :> (CanThrowMany
                                                                                                                                        '[]
                                                                                                                                      :> ("teams"
                                                                                                                                          :> (Capture
                                                                                                                                                "tid"
                                                                                                                                                TeamId
                                                                                                                                              :> ("features"
                                                                                                                                                  :> ("limitedEventFanout"
                                                                                                                                                      :> (ReqBody
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeaturePatch
                                                                                                                                                               LimitedEventFanoutConfig)
                                                                                                                                                          :> Patch
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeature
                                                                                                                                                                  LimitedEventFanoutConfig))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", SearchVisibilityInboundConfig)
         (Description ""
          :> (Summary "Get config for searchVisibilityInbound"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("searchVisibilityInbound"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SearchVisibilityInboundConfig))))))))))
       :<|> (Named
               '("iput", SearchVisibilityInboundConfig)
               (Description ""
                :> (Summary "Put config for searchVisibilityInbound"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("searchVisibilityInbound"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature
                                                                 SearchVisibilityInboundConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SearchVisibilityInboundConfig)))))))))))))
             :<|> Named
                    '("ipatch", SearchVisibilityInboundConfig)
                    (Description ""
                     :> (Summary "Patch config for searchVisibilityInbound"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("searchVisibilityInbound"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      SearchVisibilityInboundConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SearchVisibilityInboundConfig)))))))))))))))
      :<|> ((Named
               '("iget", ValidateSAMLEmailsConfig)
               (Description ""
                :> (Summary "Get config for validateSAMLemails"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("validateSAMLemails"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        ValidateSAMLEmailsConfig))))))))))
             :<|> (Named
                     '("iput", ValidateSAMLEmailsConfig)
                     (Description ""
                      :> (Summary "Put config for validateSAMLemails"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("validateSAMLemails"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       ValidateSAMLEmailsConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          ValidateSAMLEmailsConfig)))))))))))))
                   :<|> Named
                          '("ipatch", ValidateSAMLEmailsConfig)
                          (Description ""
                           :> (Summary "Patch config for validateSAMLemails"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("validateSAMLemails"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            ValidateSAMLEmailsConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               ValidateSAMLEmailsConfig)))))))))))))))
            :<|> ((Named
                     '("iget", DigitalSignaturesConfig)
                     (Description ""
                      :> (Summary "Get config for digitalSignatures"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("digitalSignatures"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              DigitalSignaturesConfig))))))))))
                   :<|> (Named
                           '("iput", DigitalSignaturesConfig)
                           (Description ""
                            :> (Summary "Put config for digitalSignatures"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("digitalSignatures"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             DigitalSignaturesConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                DigitalSignaturesConfig)))))))))))))
                         :<|> Named
                                '("ipatch", DigitalSignaturesConfig)
                                (Description ""
                                 :> (Summary "Patch config for digitalSignatures"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("digitalSignatures"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  DigitalSignaturesConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     DigitalSignaturesConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", AppLockConfig)
                           (Description ""
                            :> (Summary "Get config for appLock"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("appLock"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    AppLockConfig))))))))))
                         :<|> (Named
                                 '("iput", AppLockConfig)
                                 (Description ""
                                  :> (Summary "Put config for appLock"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("appLock"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   AppLockConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      AppLockConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", AppLockConfig)
                                      (Description ""
                                       :> (Summary "Patch config for appLock"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("appLock"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        AppLockConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           AppLockConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", FileSharingConfig)
                                 (Description ""
                                  :> (Summary "Get config for fileSharing"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("fileSharing"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          FileSharingConfig))))))))))
                               :<|> (Named
                                       '("iput", FileSharingConfig)
                                       (Description ""
                                        :> (Summary "Put config for fileSharing"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("fileSharing"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         FileSharingConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            FileSharingConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", FileSharingConfig)
                                            (Description ""
                                             :> (Summary "Patch config for fileSharing"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("fileSharing"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              FileSharingConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 FileSharingConfig)))))))))))))))
                              :<|> (Named
                                      '("iget", ClassifiedDomainsConfig)
                                      (Description ""
                                       :> (Summary "Get config for classifiedDomains"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("classifiedDomains"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               ClassifiedDomainsConfig))))))))))
                                    :<|> ((Named
                                             '("iget", ConferenceCallingConfig)
                                             (Description ""
                                              :> (Summary "Get config for conferenceCalling"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("conferenceCalling"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      ConferenceCallingConfig))))))))))
                                           :<|> (Named
                                                   '("iput", ConferenceCallingConfig)
                                                   (Description ""
                                                    :> (Summary "Put config for conferenceCalling"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("conferenceCalling"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     ConferenceCallingConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        ConferenceCallingConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", ConferenceCallingConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Patch config for conferenceCalling"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("conferenceCalling"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          ConferenceCallingConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             ConferenceCallingConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", SelfDeletingMessagesConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Get config for selfDeletingMessages"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("selfDeletingMessages"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            SelfDeletingMessagesConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", SelfDeletingMessagesConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Put config for selfDeletingMessages"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("selfDeletingMessages"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           SelfDeletingMessagesConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              SelfDeletingMessagesConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch",
                                                                SelfDeletingMessagesConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for selfDeletingMessages"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("selfDeletingMessages"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                SelfDeletingMessagesConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   SelfDeletingMessagesConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget", GuestLinksConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Get config for conversationGuestLinks"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("conversationGuestLinks"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  GuestLinksConfig))))))))))
                                                       :<|> (Named
                                                               '("iput", GuestLinksConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for conversationGuestLinks"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("conversationGuestLinks"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 GuestLinksConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    GuestLinksConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch", GuestLinksConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for conversationGuestLinks"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("conversationGuestLinks"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      GuestLinksConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         GuestLinksConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget",
                                                                 SndFactorPasswordChallengeConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Get config for sndFactorPasswordChallenge"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("sndFactorPasswordChallenge"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        SndFactorPasswordChallengeConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput",
                                                                       SndFactorPasswordChallengeConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for sndFactorPasswordChallenge"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("sndFactorPasswordChallenge"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       SndFactorPasswordChallengeConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          SndFactorPasswordChallengeConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            SndFactorPasswordChallengeConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for sndFactorPasswordChallenge"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("sndFactorPasswordChallenge"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               SndFactorPasswordChallengeConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget", MLSConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Get config for mls"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("mls"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              MLSConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput", MLSConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Put config for mls"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mls"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             MLSConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                MLSConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  MLSConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Patch config for mls"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("mls"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  MLSConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     MLSConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("iget",
                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                            :> Get
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                         :<|> (Named
                                                                                 '("iput",
                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (Feature
                                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                               :<|> Named
                                                                                      '("ipatch",
                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeaturePatch
                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                   :> Patch
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("iget",
                                                                                   OutlookCalIntegrationConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Get config for outlookCalIntegration"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("outlookCalIntegration"
                                                                                                                  :> Get
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          OutlookCalIntegrationConfig))))))))))
                                                                               :<|> (Named
                                                                                       '("iput",
                                                                                         OutlookCalIntegrationConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Put config for outlookCalIntegration"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> (CanThrow
                                                                                                              TeamFeatureError
                                                                                                            :> (CanThrowMany
                                                                                                                  '[]
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("outlookCalIntegration"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      (Feature
                                                                                                                                         OutlookCalIntegrationConfig)
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            OutlookCalIntegrationConfig)))))))))))))
                                                                                     :<|> Named
                                                                                            '("ipatch",
                                                                                              OutlookCalIntegrationConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (Summary
                                                                                                   "Patch config for outlookCalIntegration"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   TeamFeatureError
                                                                                                                 :> (CanThrowMany
                                                                                                                       '[]
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("outlookCalIntegration"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeaturePatch
                                                                                                                                              OutlookCalIntegrationConfig)
                                                                                                                                         :> Patch
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 OutlookCalIntegrationConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("iget",
                                                                                         MlsE2EIdConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Get config for mlsE2EId"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("mlsE2EId"
                                                                                                                        :> Get
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                MlsE2EIdConfig))))))))))
                                                                                     :<|> (Named
                                                                                             '("iput",
                                                                                               MlsE2EIdConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Put config for mlsE2EId"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> (CanThrow
                                                                                                                    TeamFeatureError
                                                                                                                  :> (CanThrowMany
                                                                                                                        '[]
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("mlsE2EId"
                                                                                                                                      :> (ReqBody
                                                                                                                                            '[JSON]
                                                                                                                                            (Feature
                                                                                                                                               MlsE2EIdConfig)
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  MlsE2EIdConfig)))))))))))))
                                                                                           :<|> Named
                                                                                                  '("ipatch",
                                                                                                    MlsE2EIdConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (Summary
                                                                                                         "Patch config for mlsE2EId"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         TeamFeatureError
                                                                                                                       :> (CanThrowMany
                                                                                                                             '[]
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("mlsE2EId"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                    MlsE2EIdConfig)
                                                                                                                                               :> Patch
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       MlsE2EIdConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("iget",
                                                                                               MlsMigrationConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Get config for mlsMigration"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> ("teams"
                                                                                                                  :> (Capture
                                                                                                                        "tid"
                                                                                                                        TeamId
                                                                                                                      :> ("features"
                                                                                                                          :> ("mlsMigration"
                                                                                                                              :> Get
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      MlsMigrationConfig))))))))))
                                                                                           :<|> (Named
                                                                                                   '("iput",
                                                                                                     MlsMigrationConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (Summary
                                                                                                          "Put config for mlsMigration"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> (CanThrow
                                                                                                                          TeamFeatureError
                                                                                                                        :> (CanThrowMany
                                                                                                                              '[]
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("mlsMigration"
                                                                                                                                            :> (ReqBody
                                                                                                                                                  '[JSON]
                                                                                                                                                  (Feature
                                                                                                                                                     MlsMigrationConfig)
                                                                                                                                                :> Put
                                                                                                                                                     '[JSON]
                                                                                                                                                     (LockableFeature
                                                                                                                                                        MlsMigrationConfig)))))))))))))
                                                                                                 :<|> Named
                                                                                                        '("ipatch",
                                                                                                          MlsMigrationConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (Summary
                                                                                                               "Patch config for mlsMigration"
                                                                                                             :> (CanThrow
                                                                                                                   ('MissingPermission
                                                                                                                      'Nothing)
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               TeamFeatureError
                                                                                                                             :> (CanThrowMany
                                                                                                                                   '[]
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("mlsMigration"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                          MlsMigrationConfig)
                                                                                                                                                     :> Patch
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             MlsMigrationConfig)))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("iget",
                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                   (Description
                                                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                    :> (Summary
                                                                                                          "Get config for enforceFileDownloadLocation"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> ("teams"
                                                                                                                        :> (Capture
                                                                                                                              "tid"
                                                                                                                              TeamId
                                                                                                                            :> ("features"
                                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                                    :> Get
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            EnforceFileDownloadLocationConfig))))))))))
                                                                                                 :<|> (Named
                                                                                                         '("iput",
                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                         (Description
                                                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                          :> (Summary
                                                                                                                "Put config for enforceFileDownloadLocation"
                                                                                                              :> (CanThrow
                                                                                                                    ('MissingPermission
                                                                                                                       'Nothing)
                                                                                                                  :> (CanThrow
                                                                                                                        'NotATeamMember
                                                                                                                      :> (CanThrow
                                                                                                                            'TeamNotFound
                                                                                                                          :> (CanThrow
                                                                                                                                TeamFeatureError
                                                                                                                              :> (CanThrowMany
                                                                                                                                    '[]
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                                                                  :> (ReqBody
                                                                                                                                                        '[JSON]
                                                                                                                                                        (Feature
                                                                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                                                                      :> Put
                                                                                                                                                           '[JSON]
                                                                                                                                                           (LockableFeature
                                                                                                                                                              EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                       :<|> Named
                                                                                                              '("ipatch",
                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                              (Description
                                                                                                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                               :> (Summary
                                                                                                                     "Patch config for enforceFileDownloadLocation"
                                                                                                                   :> (CanThrow
                                                                                                                         ('MissingPermission
                                                                                                                            'Nothing)
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     TeamFeatureError
                                                                                                                                   :> (CanThrowMany
                                                                                                                                         '[]
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("enforceFileDownloadLocation"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                                                           :> Patch
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                :<|> (Named
                                                                                                        '("iget",
                                                                                                          LimitedEventFanoutConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (Summary
                                                                                                               "Get config for limitedEventFanout"
                                                                                                             :> (CanThrow
                                                                                                                   ('MissingPermission
                                                                                                                      'Nothing)
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> ("teams"
                                                                                                                             :> (Capture
                                                                                                                                   "tid"
                                                                                                                                   TeamId
                                                                                                                                 :> ("features"
                                                                                                                                     :> ("limitedEventFanout"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 LimitedEventFanoutConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("iput",
                                                                                                                LimitedEventFanoutConfig)
                                                                                                              (Description
                                                                                                                 ""
                                                                                                               :> (Summary
                                                                                                                     "Put config for limitedEventFanout"
                                                                                                                   :> (CanThrow
                                                                                                                         ('MissingPermission
                                                                                                                            'Nothing)
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     TeamFeatureError
                                                                                                                                   :> (CanThrowMany
                                                                                                                                         '[]
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("limitedEventFanout"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             (Feature
                                                                                                                                                                LimitedEventFanoutConfig)
                                                                                                                                                           :> Put
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   LimitedEventFanoutConfig)))))))))))))
                                                                                                            :<|> Named
                                                                                                                   '("ipatch",
                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                   (Description
                                                                                                                      ""
                                                                                                                    :> (Summary
                                                                                                                          "Patch config for limitedEventFanout"
                                                                                                                        :> (CanThrow
                                                                                                                              ('MissingPermission
                                                                                                                                 'Nothing)
                                                                                                                            :> (CanThrow
                                                                                                                                  'NotATeamMember
                                                                                                                                :> (CanThrow
                                                                                                                                      'TeamNotFound
                                                                                                                                    :> (CanThrow
                                                                                                                                          TeamFeatureError
                                                                                                                                        :> (CanThrowMany
                                                                                                                                              '[]
                                                                                                                                            :> ("teams"
                                                                                                                                                :> (Capture
                                                                                                                                                      "tid"
                                                                                                                                                      TeamId
                                                                                                                                                    :> ("features"
                                                                                                                                                        :> ("limitedEventFanout"
                                                                                                                                                            :> (ReqBody
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeaturePatch
                                                                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                                                                :> Patch
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeature
                                                                                                                                                                        LimitedEventFanoutConfig)))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", ValidateSAMLEmailsConfig)
     (Description ""
      :> (Summary "Get config for validateSAMLemails"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("validateSAMLemails"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature ValidateSAMLEmailsConfig))))))))))
   :<|> (Named
           '("iput", ValidateSAMLEmailsConfig)
           (Description ""
            :> (Summary "Put config for validateSAMLemails"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("validateSAMLemails"
                                                    :> (ReqBody
                                                          '[JSON] (Feature ValidateSAMLEmailsConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                ValidateSAMLEmailsConfig)))))))))))))
         :<|> Named
                '("ipatch", ValidateSAMLEmailsConfig)
                (Description ""
                 :> (Summary "Patch config for validateSAMLemails"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("validateSAMLemails"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  ValidateSAMLEmailsConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     ValidateSAMLEmailsConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", ValidateSAMLEmailsConfig)
     (Description (FeatureAPIDesc ValidateSAMLEmailsConfig)
      :> (Summary
            (AppendSymbol
               "Get config for " (FeatureSymbol ValidateSAMLEmailsConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol ValidateSAMLEmailsConfig
                                      :> Get
                                           '[JSON]
                                           (LockableFeature ValidateSAMLEmailsConfig))))))))))
   :<|> (Named
           '("iput", ValidateSAMLEmailsConfig)
           (Description (FeatureAPIDesc ValidateSAMLEmailsConfig)
            :> (Summary
                  (AppendSymbol
                     "Put config for " (FeatureSymbol ValidateSAMLEmailsConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors ValidateSAMLEmailsConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol ValidateSAMLEmailsConfig
                                                    :> (ReqBody
                                                          '[JSON] (Feature ValidateSAMLEmailsConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                ValidateSAMLEmailsConfig)))))))))))))
         :<|> Named
                '("ipatch", ValidateSAMLEmailsConfig)
                (Description (FeatureAPIDesc ValidateSAMLEmailsConfig)
                 :> (Summary
                       (AppendSymbol
                          "Patch config for " (FeatureSymbol ValidateSAMLEmailsConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany (FeatureErrors ValidateSAMLEmailsConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol ValidateSAMLEmailsConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  ValidateSAMLEmailsConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     ValidateSAMLEmailsConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", ValidateSAMLEmailsConfig)
     (Description ""
      :> (Summary "Get config for validateSAMLemails"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("validateSAMLemails"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature ValidateSAMLEmailsConfig))))))))))
   :<|> (Named
           '("iput", ValidateSAMLEmailsConfig)
           (Description ""
            :> (Summary "Put config for validateSAMLemails"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("validateSAMLemails"
                                                    :> (ReqBody
                                                          '[JSON] (Feature ValidateSAMLEmailsConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                ValidateSAMLEmailsConfig)))))))))))))
         :<|> Named
                '("ipatch", ValidateSAMLEmailsConfig)
                (Description ""
                 :> (Summary "Patch config for validateSAMLemails"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("validateSAMLemails"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  ValidateSAMLEmailsConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     ValidateSAMLEmailsConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", DigitalSignaturesConfig)
         (Description ""
          :> (Summary "Get config for digitalSignatures"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("digitalSignatures"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature DigitalSignaturesConfig))))))))))
       :<|> (Named
               '("iput", DigitalSignaturesConfig)
               (Description ""
                :> (Summary "Put config for digitalSignatures"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("digitalSignatures"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature DigitalSignaturesConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    DigitalSignaturesConfig)))))))))))))
             :<|> Named
                    '("ipatch", DigitalSignaturesConfig)
                    (Description ""
                     :> (Summary "Patch config for digitalSignatures"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("digitalSignatures"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      DigitalSignaturesConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         DigitalSignaturesConfig)))))))))))))))
      :<|> ((Named
               '("iget", AppLockConfig)
               (Description ""
                :> (Summary "Get config for appLock"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("appLock"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature AppLockConfig))))))))))
             :<|> (Named
                     '("iput", AppLockConfig)
                     (Description ""
                      :> (Summary "Put config for appLock"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("appLock"
                                                              :> (ReqBody
                                                                    '[JSON] (Feature AppLockConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          AppLockConfig)))))))))))))
                   :<|> Named
                          '("ipatch", AppLockConfig)
                          (Description ""
                           :> (Summary "Patch config for appLock"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("appLock"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            AppLockConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               AppLockConfig)))))))))))))))
            :<|> ((Named
                     '("iget", FileSharingConfig)
                     (Description ""
                      :> (Summary "Get config for fileSharing"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("fileSharing"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              FileSharingConfig))))))))))
                   :<|> (Named
                           '("iput", FileSharingConfig)
                           (Description ""
                            :> (Summary "Put config for fileSharing"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("fileSharing"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             FileSharingConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                FileSharingConfig)))))))))))))
                         :<|> Named
                                '("ipatch", FileSharingConfig)
                                (Description ""
                                 :> (Summary "Patch config for fileSharing"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("fileSharing"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  FileSharingConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     FileSharingConfig)))))))))))))))
                  :<|> (Named
                          '("iget", ClassifiedDomainsConfig)
                          (Description ""
                           :> (Summary "Get config for classifiedDomains"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("classifiedDomains"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   ClassifiedDomainsConfig))))))))))
                        :<|> ((Named
                                 '("iget", ConferenceCallingConfig)
                                 (Description ""
                                  :> (Summary "Get config for conferenceCalling"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("conferenceCalling"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          ConferenceCallingConfig))))))))))
                               :<|> (Named
                                       '("iput", ConferenceCallingConfig)
                                       (Description ""
                                        :> (Summary "Put config for conferenceCalling"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("conferenceCalling"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         ConferenceCallingConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            ConferenceCallingConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", ConferenceCallingConfig)
                                            (Description ""
                                             :> (Summary "Patch config for conferenceCalling"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("conferenceCalling"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              ConferenceCallingConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 ConferenceCallingConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", SelfDeletingMessagesConfig)
                                       (Description ""
                                        :> (Summary "Get config for selfDeletingMessages"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("selfDeletingMessages"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                SelfDeletingMessagesConfig))))))))))
                                     :<|> (Named
                                             '("iput", SelfDeletingMessagesConfig)
                                             (Description ""
                                              :> (Summary "Put config for selfDeletingMessages"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("selfDeletingMessages"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               SelfDeletingMessagesConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  SelfDeletingMessagesConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", SelfDeletingMessagesConfig)
                                                  (Description ""
                                                   :> (Summary
                                                         "Patch config for selfDeletingMessages"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("selfDeletingMessages"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    SelfDeletingMessagesConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       SelfDeletingMessagesConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", GuestLinksConfig)
                                             (Description ""
                                              :> (Summary "Get config for conversationGuestLinks"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("conversationGuestLinks"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      GuestLinksConfig))))))))))
                                           :<|> (Named
                                                   '("iput", GuestLinksConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Put config for conversationGuestLinks"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("conversationGuestLinks"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     GuestLinksConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        GuestLinksConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", GuestLinksConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Patch config for conversationGuestLinks"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("conversationGuestLinks"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          GuestLinksConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             GuestLinksConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", SndFactorPasswordChallengeConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Get config for sndFactorPasswordChallenge"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("sndFactorPasswordChallenge"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            SndFactorPasswordChallengeConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", SndFactorPasswordChallengeConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Put config for sndFactorPasswordChallenge"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("sndFactorPasswordChallenge"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           SndFactorPasswordChallengeConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              SndFactorPasswordChallengeConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch",
                                                                SndFactorPasswordChallengeConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for sndFactorPasswordChallenge"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   SndFactorPasswordChallengeConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget", MLSConfig)
                                                         (Description ""
                                                          :> (Summary "Get config for mls"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("mls"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  MLSConfig))))))))))
                                                       :<|> (Named
                                                               '("iput", MLSConfig)
                                                               (Description ""
                                                                :> (Summary "Put config for mls"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mls"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 MLSConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    MLSConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch", MLSConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for mls"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("mls"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      MLSConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         MLSConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget",
                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Get config for exposeInvitationURLsToTeamAdmin"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput",
                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for exposeInvitationURLsToTeamAdmin"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget",
                                                                       OutlookCalIntegrationConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Get config for outlookCalIntegration"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("outlookCalIntegration"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              OutlookCalIntegrationConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput",
                                                                             OutlookCalIntegrationConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Put config for outlookCalIntegration"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("outlookCalIntegration"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             OutlookCalIntegrationConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                OutlookCalIntegrationConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  OutlookCalIntegrationConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Patch config for outlookCalIntegration"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("outlookCalIntegration"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  OutlookCalIntegrationConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     OutlookCalIntegrationConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("iget", MlsE2EIdConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Get config for mlsE2EId"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("mlsE2EId"
                                                                                                            :> Get
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    MlsE2EIdConfig))))))))))
                                                                         :<|> (Named
                                                                                 '("iput",
                                                                                   MlsE2EIdConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Put config for mlsE2EId"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mlsE2EId"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (Feature
                                                                                                                                   MlsE2EIdConfig)
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      MlsE2EIdConfig)))))))))))))
                                                                               :<|> Named
                                                                                      '("ipatch",
                                                                                        MlsE2EIdConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Patch config for mlsE2EId"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("mlsE2EId"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeaturePatch
                                                                                                                                        MlsE2EIdConfig)
                                                                                                                                   :> Patch
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           MlsE2EIdConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("iget",
                                                                                   MlsMigrationConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Get config for mlsMigration"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("mlsMigration"
                                                                                                                  :> Get
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          MlsMigrationConfig))))))))))
                                                                               :<|> (Named
                                                                                       '("iput",
                                                                                         MlsMigrationConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Put config for mlsMigration"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> (CanThrow
                                                                                                              TeamFeatureError
                                                                                                            :> (CanThrowMany
                                                                                                                  '[]
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mlsMigration"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      (Feature
                                                                                                                                         MlsMigrationConfig)
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            MlsMigrationConfig)))))))))))))
                                                                                     :<|> Named
                                                                                            '("ipatch",
                                                                                              MlsMigrationConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (Summary
                                                                                                   "Patch config for mlsMigration"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   TeamFeatureError
                                                                                                                 :> (CanThrowMany
                                                                                                                       '[]
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("mlsMigration"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeaturePatch
                                                                                                                                              MlsMigrationConfig)
                                                                                                                                         :> Patch
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 MlsMigrationConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("iget",
                                                                                         EnforceFileDownloadLocationConfig)
                                                                                       (Description
                                                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                        :> (Summary
                                                                                              "Get config for enforceFileDownloadLocation"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                                        :> Get
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                EnforceFileDownloadLocationConfig))))))))))
                                                                                     :<|> (Named
                                                                                             '("iput",
                                                                                               EnforceFileDownloadLocationConfig)
                                                                                             (Description
                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                              :> (Summary
                                                                                                    "Put config for enforceFileDownloadLocation"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> (CanThrow
                                                                                                                    TeamFeatureError
                                                                                                                  :> (CanThrowMany
                                                                                                                        '[]
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                      :> (ReqBody
                                                                                                                                            '[JSON]
                                                                                                                                            (Feature
                                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  EnforceFileDownloadLocationConfig)))))))))))))
                                                                                           :<|> Named
                                                                                                  '("ipatch",
                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                  (Description
                                                                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                   :> (Summary
                                                                                                         "Patch config for enforceFileDownloadLocation"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         TeamFeatureError
                                                                                                                       :> (CanThrowMany
                                                                                                                             '[]
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("enforceFileDownloadLocation"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                                               :> Patch
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                    :<|> (Named
                                                                                            '("iget",
                                                                                              LimitedEventFanoutConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (Summary
                                                                                                   "Get config for limitedEventFanout"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("limitedEventFanout"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     LimitedEventFanoutConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("iput",
                                                                                                    LimitedEventFanoutConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (Summary
                                                                                                         "Put config for limitedEventFanout"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         TeamFeatureError
                                                                                                                       :> (CanThrowMany
                                                                                                                             '[]
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("limitedEventFanout"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 (Feature
                                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                               :> Put
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       LimitedEventFanoutConfig)))))))))))))
                                                                                                :<|> Named
                                                                                                       '("ipatch",
                                                                                                         LimitedEventFanoutConfig)
                                                                                                       (Description
                                                                                                          ""
                                                                                                        :> (Summary
                                                                                                              "Patch config for limitedEventFanout"
                                                                                                            :> (CanThrow
                                                                                                                  ('MissingPermission
                                                                                                                     'Nothing)
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          'TeamNotFound
                                                                                                                        :> (CanThrow
                                                                                                                              TeamFeatureError
                                                                                                                            :> (CanThrowMany
                                                                                                                                  '[]
                                                                                                                                :> ("teams"
                                                                                                                                    :> (Capture
                                                                                                                                          "tid"
                                                                                                                                          TeamId
                                                                                                                                        :> ("features"
                                                                                                                                            :> ("limitedEventFanout"
                                                                                                                                                :> (ReqBody
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeaturePatch
                                                                                                                                                         LimitedEventFanoutConfig)
                                                                                                                                                    :> Patch
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeature
                                                                                                                                                            LimitedEventFanoutConfig)))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", ValidateSAMLEmailsConfig)
         (Description ""
          :> (Summary "Get config for validateSAMLemails"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("validateSAMLemails"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature ValidateSAMLEmailsConfig))))))))))
       :<|> (Named
               '("iput", ValidateSAMLEmailsConfig)
               (Description ""
                :> (Summary "Put config for validateSAMLemails"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("validateSAMLemails"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature ValidateSAMLEmailsConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    ValidateSAMLEmailsConfig)))))))))))))
             :<|> Named
                    '("ipatch", ValidateSAMLEmailsConfig)
                    (Description ""
                     :> (Summary "Patch config for validateSAMLemails"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("validateSAMLemails"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      ValidateSAMLEmailsConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         ValidateSAMLEmailsConfig)))))))))))))))
      :<|> ((Named
               '("iget", DigitalSignaturesConfig)
               (Description ""
                :> (Summary "Get config for digitalSignatures"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("digitalSignatures"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        DigitalSignaturesConfig))))))))))
             :<|> (Named
                     '("iput", DigitalSignaturesConfig)
                     (Description ""
                      :> (Summary "Put config for digitalSignatures"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("digitalSignatures"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       DigitalSignaturesConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          DigitalSignaturesConfig)))))))))))))
                   :<|> Named
                          '("ipatch", DigitalSignaturesConfig)
                          (Description ""
                           :> (Summary "Patch config for digitalSignatures"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("digitalSignatures"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            DigitalSignaturesConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               DigitalSignaturesConfig)))))))))))))))
            :<|> ((Named
                     '("iget", AppLockConfig)
                     (Description ""
                      :> (Summary "Get config for appLock"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("appLock"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature AppLockConfig))))))))))
                   :<|> (Named
                           '("iput", AppLockConfig)
                           (Description ""
                            :> (Summary "Put config for appLock"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("appLock"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature AppLockConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                AppLockConfig)))))))))))))
                         :<|> Named
                                '("ipatch", AppLockConfig)
                                (Description ""
                                 :> (Summary "Patch config for appLock"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("appLock"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  AppLockConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     AppLockConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", FileSharingConfig)
                           (Description ""
                            :> (Summary "Get config for fileSharing"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("fileSharing"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    FileSharingConfig))))))))))
                         :<|> (Named
                                 '("iput", FileSharingConfig)
                                 (Description ""
                                  :> (Summary "Put config for fileSharing"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("fileSharing"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   FileSharingConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      FileSharingConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", FileSharingConfig)
                                      (Description ""
                                       :> (Summary "Patch config for fileSharing"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("fileSharing"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        FileSharingConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           FileSharingConfig)))))))))))))))
                        :<|> (Named
                                '("iget", ClassifiedDomainsConfig)
                                (Description ""
                                 :> (Summary "Get config for classifiedDomains"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("classifiedDomains"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         ClassifiedDomainsConfig))))))))))
                              :<|> ((Named
                                       '("iget", ConferenceCallingConfig)
                                       (Description ""
                                        :> (Summary "Get config for conferenceCalling"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("conferenceCalling"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                ConferenceCallingConfig))))))))))
                                     :<|> (Named
                                             '("iput", ConferenceCallingConfig)
                                             (Description ""
                                              :> (Summary "Put config for conferenceCalling"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("conferenceCalling"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               ConferenceCallingConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  ConferenceCallingConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", ConferenceCallingConfig)
                                                  (Description ""
                                                   :> (Summary "Patch config for conferenceCalling"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("conferenceCalling"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    ConferenceCallingConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       ConferenceCallingConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", SelfDeletingMessagesConfig)
                                             (Description ""
                                              :> (Summary "Get config for selfDeletingMessages"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("selfDeletingMessages"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      SelfDeletingMessagesConfig))))))))))
                                           :<|> (Named
                                                   '("iput", SelfDeletingMessagesConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Put config for selfDeletingMessages"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("selfDeletingMessages"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     SelfDeletingMessagesConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        SelfDeletingMessagesConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", SelfDeletingMessagesConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Patch config for selfDeletingMessages"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("selfDeletingMessages"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          SelfDeletingMessagesConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             SelfDeletingMessagesConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", GuestLinksConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Get config for conversationGuestLinks"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("conversationGuestLinks"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            GuestLinksConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", GuestLinksConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Put config for conversationGuestLinks"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("conversationGuestLinks"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           GuestLinksConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              GuestLinksConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch", GuestLinksConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for conversationGuestLinks"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("conversationGuestLinks"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                GuestLinksConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   GuestLinksConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget", SndFactorPasswordChallengeConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Get config for sndFactorPasswordChallenge"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("sndFactorPasswordChallenge"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  SndFactorPasswordChallengeConfig))))))))))
                                                       :<|> (Named
                                                               '("iput",
                                                                 SndFactorPasswordChallengeConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for sndFactorPasswordChallenge"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("sndFactorPasswordChallenge"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 SndFactorPasswordChallengeConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    SndFactorPasswordChallengeConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch",
                                                                      SndFactorPasswordChallengeConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for sndFactorPasswordChallenge"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         SndFactorPasswordChallengeConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget", MLSConfig)
                                                               (Description ""
                                                                :> (Summary "Get config for mls"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("mls"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        MLSConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput", MLSConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for mls"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mls"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       MLSConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          MLSConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch", MLSConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for mls"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("mls"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            MLSConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               MLSConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget",
                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Get config for exposeInvitationURLsToTeamAdmin"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput",
                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("iget",
                                                                             OutlookCalIntegrationConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Get config for outlookCalIntegration"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("outlookCalIntegration"
                                                                                                            :> Get
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    OutlookCalIntegrationConfig))))))))))
                                                                         :<|> (Named
                                                                                 '("iput",
                                                                                   OutlookCalIntegrationConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Put config for outlookCalIntegration"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("outlookCalIntegration"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (Feature
                                                                                                                                   OutlookCalIntegrationConfig)
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      OutlookCalIntegrationConfig)))))))))))))
                                                                               :<|> Named
                                                                                      '("ipatch",
                                                                                        OutlookCalIntegrationConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Patch config for outlookCalIntegration"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("outlookCalIntegration"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeaturePatch
                                                                                                                                        OutlookCalIntegrationConfig)
                                                                                                                                   :> Patch
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           OutlookCalIntegrationConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("iget",
                                                                                   MlsE2EIdConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Get config for mlsE2EId"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("mlsE2EId"
                                                                                                                  :> Get
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          MlsE2EIdConfig))))))))))
                                                                               :<|> (Named
                                                                                       '("iput",
                                                                                         MlsE2EIdConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Put config for mlsE2EId"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> (CanThrow
                                                                                                              TeamFeatureError
                                                                                                            :> (CanThrowMany
                                                                                                                  '[]
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mlsE2EId"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      (Feature
                                                                                                                                         MlsE2EIdConfig)
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            MlsE2EIdConfig)))))))))))))
                                                                                     :<|> Named
                                                                                            '("ipatch",
                                                                                              MlsE2EIdConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (Summary
                                                                                                   "Patch config for mlsE2EId"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   TeamFeatureError
                                                                                                                 :> (CanThrowMany
                                                                                                                       '[]
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("mlsE2EId"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeaturePatch
                                                                                                                                              MlsE2EIdConfig)
                                                                                                                                         :> Patch
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 MlsE2EIdConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("iget",
                                                                                         MlsMigrationConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Get config for mlsMigration"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("mlsMigration"
                                                                                                                        :> Get
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                MlsMigrationConfig))))))))))
                                                                                     :<|> (Named
                                                                                             '("iput",
                                                                                               MlsMigrationConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Put config for mlsMigration"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> (CanThrow
                                                                                                                    TeamFeatureError
                                                                                                                  :> (CanThrowMany
                                                                                                                        '[]
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("mlsMigration"
                                                                                                                                      :> (ReqBody
                                                                                                                                            '[JSON]
                                                                                                                                            (Feature
                                                                                                                                               MlsMigrationConfig)
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  MlsMigrationConfig)))))))))))))
                                                                                           :<|> Named
                                                                                                  '("ipatch",
                                                                                                    MlsMigrationConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (Summary
                                                                                                         "Patch config for mlsMigration"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         TeamFeatureError
                                                                                                                       :> (CanThrowMany
                                                                                                                             '[]
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("mlsMigration"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                    MlsMigrationConfig)
                                                                                                                                               :> Patch
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       MlsMigrationConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("iget",
                                                                                               EnforceFileDownloadLocationConfig)
                                                                                             (Description
                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                              :> (Summary
                                                                                                    "Get config for enforceFileDownloadLocation"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> ("teams"
                                                                                                                  :> (Capture
                                                                                                                        "tid"
                                                                                                                        TeamId
                                                                                                                      :> ("features"
                                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                                              :> Get
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      EnforceFileDownloadLocationConfig))))))))))
                                                                                           :<|> (Named
                                                                                                   '("iput",
                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                   (Description
                                                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                    :> (Summary
                                                                                                          "Put config for enforceFileDownloadLocation"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> (CanThrow
                                                                                                                          TeamFeatureError
                                                                                                                        :> (CanThrowMany
                                                                                                                              '[]
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("enforceFileDownloadLocation"
                                                                                                                                            :> (ReqBody
                                                                                                                                                  '[JSON]
                                                                                                                                                  (Feature
                                                                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                                                                :> Put
                                                                                                                                                     '[JSON]
                                                                                                                                                     (LockableFeature
                                                                                                                                                        EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                 :<|> Named
                                                                                                        '("ipatch",
                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                        (Description
                                                                                                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                         :> (Summary
                                                                                                               "Patch config for enforceFileDownloadLocation"
                                                                                                             :> (CanThrow
                                                                                                                   ('MissingPermission
                                                                                                                      'Nothing)
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               TeamFeatureError
                                                                                                                             :> (CanThrowMany
                                                                                                                                   '[]
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("enforceFileDownloadLocation"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeaturePatch
                                                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                                                     :> Patch
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                          :<|> (Named
                                                                                                  '("iget",
                                                                                                    LimitedEventFanoutConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (Summary
                                                                                                         "Get config for limitedEventFanout"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> ("teams"
                                                                                                                       :> (Capture
                                                                                                                             "tid"
                                                                                                                             TeamId
                                                                                                                           :> ("features"
                                                                                                                               :> ("limitedEventFanout"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           LimitedEventFanoutConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("iput",
                                                                                                          LimitedEventFanoutConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (Summary
                                                                                                               "Put config for limitedEventFanout"
                                                                                                             :> (CanThrow
                                                                                                                   ('MissingPermission
                                                                                                                      'Nothing)
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               TeamFeatureError
                                                                                                                             :> (CanThrowMany
                                                                                                                                   '[]
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("limitedEventFanout"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       (Feature
                                                                                                                                                          LimitedEventFanoutConfig)
                                                                                                                                                     :> Put
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             LimitedEventFanoutConfig)))))))))))))
                                                                                                      :<|> Named
                                                                                                             '("ipatch",
                                                                                                               LimitedEventFanoutConfig)
                                                                                                             (Description
                                                                                                                ""
                                                                                                              :> (Summary
                                                                                                                    "Patch config for limitedEventFanout"
                                                                                                                  :> (CanThrow
                                                                                                                        ('MissingPermission
                                                                                                                           'Nothing)
                                                                                                                      :> (CanThrow
                                                                                                                            'NotATeamMember
                                                                                                                          :> (CanThrow
                                                                                                                                'TeamNotFound
                                                                                                                              :> (CanThrow
                                                                                                                                    TeamFeatureError
                                                                                                                                  :> (CanThrowMany
                                                                                                                                        '[]
                                                                                                                                      :> ("teams"
                                                                                                                                          :> (Capture
                                                                                                                                                "tid"
                                                                                                                                                TeamId
                                                                                                                                              :> ("features"
                                                                                                                                                  :> ("limitedEventFanout"
                                                                                                                                                      :> (ReqBody
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeaturePatch
                                                                                                                                                               LimitedEventFanoutConfig)
                                                                                                                                                          :> Patch
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeature
                                                                                                                                                                  LimitedEventFanoutConfig))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", DigitalSignaturesConfig)
     (Description ""
      :> (Summary "Get config for digitalSignatures"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("digitalSignatures"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature DigitalSignaturesConfig))))))))))
   :<|> (Named
           '("iput", DigitalSignaturesConfig)
           (Description ""
            :> (Summary "Put config for digitalSignatures"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("digitalSignatures"
                                                    :> (ReqBody
                                                          '[JSON] (Feature DigitalSignaturesConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                DigitalSignaturesConfig)))))))))))))
         :<|> Named
                '("ipatch", DigitalSignaturesConfig)
                (Description ""
                 :> (Summary "Patch config for digitalSignatures"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("digitalSignatures"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  DigitalSignaturesConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     DigitalSignaturesConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", DigitalSignaturesConfig)
     (Description (FeatureAPIDesc DigitalSignaturesConfig)
      :> (Summary
            (AppendSymbol
               "Get config for " (FeatureSymbol DigitalSignaturesConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol DigitalSignaturesConfig
                                      :> Get
                                           '[JSON]
                                           (LockableFeature DigitalSignaturesConfig))))))))))
   :<|> (Named
           '("iput", DigitalSignaturesConfig)
           (Description (FeatureAPIDesc DigitalSignaturesConfig)
            :> (Summary
                  (AppendSymbol
                     "Put config for " (FeatureSymbol DigitalSignaturesConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors DigitalSignaturesConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol DigitalSignaturesConfig
                                                    :> (ReqBody
                                                          '[JSON] (Feature DigitalSignaturesConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                DigitalSignaturesConfig)))))))))))))
         :<|> Named
                '("ipatch", DigitalSignaturesConfig)
                (Description (FeatureAPIDesc DigitalSignaturesConfig)
                 :> (Summary
                       (AppendSymbol
                          "Patch config for " (FeatureSymbol DigitalSignaturesConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany (FeatureErrors DigitalSignaturesConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol DigitalSignaturesConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  DigitalSignaturesConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     DigitalSignaturesConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", DigitalSignaturesConfig)
     (Description ""
      :> (Summary "Get config for digitalSignatures"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("digitalSignatures"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature DigitalSignaturesConfig))))))))))
   :<|> (Named
           '("iput", DigitalSignaturesConfig)
           (Description ""
            :> (Summary "Put config for digitalSignatures"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("digitalSignatures"
                                                    :> (ReqBody
                                                          '[JSON] (Feature DigitalSignaturesConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                DigitalSignaturesConfig)))))))))))))
         :<|> Named
                '("ipatch", DigitalSignaturesConfig)
                (Description ""
                 :> (Summary "Patch config for digitalSignatures"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("digitalSignatures"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  DigitalSignaturesConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     DigitalSignaturesConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", AppLockConfig)
         (Description ""
          :> (Summary "Get config for appLock"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("appLock"
                                          :> Get '[JSON] (LockableFeature AppLockConfig))))))))))
       :<|> (Named
               '("iput", AppLockConfig)
               (Description ""
                :> (Summary "Put config for appLock"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("appLock"
                                                        :> (ReqBody '[JSON] (Feature AppLockConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    AppLockConfig)))))))))))))
             :<|> Named
                    '("ipatch", AppLockConfig)
                    (Description ""
                     :> (Summary "Patch config for appLock"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("appLock"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      AppLockConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         AppLockConfig)))))))))))))))
      :<|> ((Named
               '("iget", FileSharingConfig)
               (Description ""
                :> (Summary "Get config for fileSharing"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("fileSharing"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature FileSharingConfig))))))))))
             :<|> (Named
                     '("iput", FileSharingConfig)
                     (Description ""
                      :> (Summary "Put config for fileSharing"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("fileSharing"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature FileSharingConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          FileSharingConfig)))))))))))))
                   :<|> Named
                          '("ipatch", FileSharingConfig)
                          (Description ""
                           :> (Summary "Patch config for fileSharing"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("fileSharing"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            FileSharingConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               FileSharingConfig)))))))))))))))
            :<|> (Named
                    '("iget", ClassifiedDomainsConfig)
                    (Description ""
                     :> (Summary "Get config for classifiedDomains"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> ("teams"
                                         :> (Capture "tid" TeamId
                                             :> ("features"
                                                 :> ("classifiedDomains"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             ClassifiedDomainsConfig))))))))))
                  :<|> ((Named
                           '("iget", ConferenceCallingConfig)
                           (Description ""
                            :> (Summary "Get config for conferenceCalling"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("conferenceCalling"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    ConferenceCallingConfig))))))))))
                         :<|> (Named
                                 '("iput", ConferenceCallingConfig)
                                 (Description ""
                                  :> (Summary "Put config for conferenceCalling"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("conferenceCalling"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   ConferenceCallingConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      ConferenceCallingConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", ConferenceCallingConfig)
                                      (Description ""
                                       :> (Summary "Patch config for conferenceCalling"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("conferenceCalling"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        ConferenceCallingConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           ConferenceCallingConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", SelfDeletingMessagesConfig)
                                 (Description ""
                                  :> (Summary "Get config for selfDeletingMessages"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("selfDeletingMessages"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          SelfDeletingMessagesConfig))))))))))
                               :<|> (Named
                                       '("iput", SelfDeletingMessagesConfig)
                                       (Description ""
                                        :> (Summary "Put config for selfDeletingMessages"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("selfDeletingMessages"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         SelfDeletingMessagesConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            SelfDeletingMessagesConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", SelfDeletingMessagesConfig)
                                            (Description ""
                                             :> (Summary "Patch config for selfDeletingMessages"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("selfDeletingMessages"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              SelfDeletingMessagesConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 SelfDeletingMessagesConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", GuestLinksConfig)
                                       (Description ""
                                        :> (Summary "Get config for conversationGuestLinks"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("conversationGuestLinks"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                GuestLinksConfig))))))))))
                                     :<|> (Named
                                             '("iput", GuestLinksConfig)
                                             (Description ""
                                              :> (Summary "Put config for conversationGuestLinks"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("conversationGuestLinks"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               GuestLinksConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  GuestLinksConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", GuestLinksConfig)
                                                  (Description ""
                                                   :> (Summary
                                                         "Patch config for conversationGuestLinks"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("conversationGuestLinks"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    GuestLinksConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       GuestLinksConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", SndFactorPasswordChallengeConfig)
                                             (Description ""
                                              :> (Summary
                                                    "Get config for sndFactorPasswordChallenge"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("sndFactorPasswordChallenge"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      SndFactorPasswordChallengeConfig))))))))))
                                           :<|> (Named
                                                   '("iput", SndFactorPasswordChallengeConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Put config for sndFactorPasswordChallenge"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("sndFactorPasswordChallenge"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     SndFactorPasswordChallengeConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        SndFactorPasswordChallengeConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch",
                                                          SndFactorPasswordChallengeConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Patch config for sndFactorPasswordChallenge"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("sndFactorPasswordChallenge"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          SndFactorPasswordChallengeConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             SndFactorPasswordChallengeConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", MLSConfig)
                                                   (Description ""
                                                    :> (Summary "Get config for mls"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("mls"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            MLSConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", MLSConfig)
                                                         (Description ""
                                                          :> (Summary "Put config for mls"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mls"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           MLSConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              MLSConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch", MLSConfig)
                                                              (Description ""
                                                               :> (Summary "Patch config for mls"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("mls"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                MLSConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   MLSConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget",
                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Get config for exposeInvitationURLsToTeamAdmin"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                       :<|> (Named
                                                               '("iput",
                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for exposeInvitationURLsToTeamAdmin"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch",
                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget",
                                                                 OutlookCalIntegrationConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Get config for outlookCalIntegration"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("outlookCalIntegration"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        OutlookCalIntegrationConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput",
                                                                       OutlookCalIntegrationConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for outlookCalIntegration"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("outlookCalIntegration"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       OutlookCalIntegrationConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          OutlookCalIntegrationConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            OutlookCalIntegrationConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for outlookCalIntegration"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("outlookCalIntegration"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            OutlookCalIntegrationConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               OutlookCalIntegrationConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget", MlsE2EIdConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Get config for mlsE2EId"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("mlsE2EId"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              MlsE2EIdConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput", MlsE2EIdConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Put config for mlsE2EId"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mlsE2EId"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             MlsE2EIdConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                MlsE2EIdConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  MlsE2EIdConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Patch config for mlsE2EId"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("mlsE2EId"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  MlsE2EIdConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     MlsE2EIdConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("iget",
                                                                             MlsMigrationConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Get config for mlsMigration"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("mlsMigration"
                                                                                                            :> Get
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    MlsMigrationConfig))))))))))
                                                                         :<|> (Named
                                                                                 '("iput",
                                                                                   MlsMigrationConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Put config for mlsMigration"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mlsMigration"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (Feature
                                                                                                                                   MlsMigrationConfig)
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      MlsMigrationConfig)))))))))))))
                                                                               :<|> Named
                                                                                      '("ipatch",
                                                                                        MlsMigrationConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Patch config for mlsMigration"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("mlsMigration"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeaturePatch
                                                                                                                                        MlsMigrationConfig)
                                                                                                                                   :> Patch
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           MlsMigrationConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("iget",
                                                                                   EnforceFileDownloadLocationConfig)
                                                                                 (Description
                                                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                  :> (Summary
                                                                                        "Get config for enforceFileDownloadLocation"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                                  :> Get
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          EnforceFileDownloadLocationConfig))))))))))
                                                                               :<|> (Named
                                                                                       '("iput",
                                                                                         EnforceFileDownloadLocationConfig)
                                                                                       (Description
                                                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                        :> (Summary
                                                                                              "Put config for enforceFileDownloadLocation"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> (CanThrow
                                                                                                              TeamFeatureError
                                                                                                            :> (CanThrowMany
                                                                                                                  '[]
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      (Feature
                                                                                                                                         EnforceFileDownloadLocationConfig)
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            EnforceFileDownloadLocationConfig)))))))))))))
                                                                                     :<|> Named
                                                                                            '("ipatch",
                                                                                              EnforceFileDownloadLocationConfig)
                                                                                            (Description
                                                                                               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                             :> (Summary
                                                                                                   "Patch config for enforceFileDownloadLocation"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   TeamFeatureError
                                                                                                                 :> (CanThrowMany
                                                                                                                       '[]
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("enforceFileDownloadLocation"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeaturePatch
                                                                                                                                              EnforceFileDownloadLocationConfig)
                                                                                                                                         :> Patch
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 EnforceFileDownloadLocationConfig)))))))))))))))
                                                                              :<|> (Named
                                                                                      '("iget",
                                                                                        LimitedEventFanoutConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Get config for limitedEventFanout"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("limitedEventFanout"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               LimitedEventFanoutConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("iput",
                                                                                              LimitedEventFanoutConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (Summary
                                                                                                   "Put config for limitedEventFanout"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   TeamFeatureError
                                                                                                                 :> (CanThrowMany
                                                                                                                       '[]
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("limitedEventFanout"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           (Feature
                                                                                                                                              LimitedEventFanoutConfig)
                                                                                                                                         :> Put
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 LimitedEventFanoutConfig)))))))))))))
                                                                                          :<|> Named
                                                                                                 '("ipatch",
                                                                                                   LimitedEventFanoutConfig)
                                                                                                 (Description
                                                                                                    ""
                                                                                                  :> (Summary
                                                                                                        "Patch config for limitedEventFanout"
                                                                                                      :> (CanThrow
                                                                                                            ('MissingPermission
                                                                                                               'Nothing)
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> (CanThrow
                                                                                                                        TeamFeatureError
                                                                                                                      :> (CanThrowMany
                                                                                                                            '[]
                                                                                                                          :> ("teams"
                                                                                                                              :> (Capture
                                                                                                                                    "tid"
                                                                                                                                    TeamId
                                                                                                                                  :> ("features"
                                                                                                                                      :> ("limitedEventFanout"
                                                                                                                                          :> (ReqBody
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeaturePatch
                                                                                                                                                   LimitedEventFanoutConfig)
                                                                                                                                              :> Patch
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeature
                                                                                                                                                      LimitedEventFanoutConfig))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", DigitalSignaturesConfig)
         (Description ""
          :> (Summary "Get config for digitalSignatures"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("digitalSignatures"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature DigitalSignaturesConfig))))))))))
       :<|> (Named
               '("iput", DigitalSignaturesConfig)
               (Description ""
                :> (Summary "Put config for digitalSignatures"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("digitalSignatures"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature DigitalSignaturesConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    DigitalSignaturesConfig)))))))))))))
             :<|> Named
                    '("ipatch", DigitalSignaturesConfig)
                    (Description ""
                     :> (Summary "Patch config for digitalSignatures"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("digitalSignatures"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      DigitalSignaturesConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         DigitalSignaturesConfig)))))))))))))))
      :<|> ((Named
               '("iget", AppLockConfig)
               (Description ""
                :> (Summary "Get config for appLock"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("appLock"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature AppLockConfig))))))))))
             :<|> (Named
                     '("iput", AppLockConfig)
                     (Description ""
                      :> (Summary "Put config for appLock"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("appLock"
                                                              :> (ReqBody
                                                                    '[JSON] (Feature AppLockConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          AppLockConfig)))))))))))))
                   :<|> Named
                          '("ipatch", AppLockConfig)
                          (Description ""
                           :> (Summary "Patch config for appLock"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("appLock"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            AppLockConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               AppLockConfig)))))))))))))))
            :<|> ((Named
                     '("iget", FileSharingConfig)
                     (Description ""
                      :> (Summary "Get config for fileSharing"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("fileSharing"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              FileSharingConfig))))))))))
                   :<|> (Named
                           '("iput", FileSharingConfig)
                           (Description ""
                            :> (Summary "Put config for fileSharing"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("fileSharing"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             FileSharingConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                FileSharingConfig)))))))))))))
                         :<|> Named
                                '("ipatch", FileSharingConfig)
                                (Description ""
                                 :> (Summary "Patch config for fileSharing"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("fileSharing"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  FileSharingConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     FileSharingConfig)))))))))))))))
                  :<|> (Named
                          '("iget", ClassifiedDomainsConfig)
                          (Description ""
                           :> (Summary "Get config for classifiedDomains"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("classifiedDomains"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   ClassifiedDomainsConfig))))))))))
                        :<|> ((Named
                                 '("iget", ConferenceCallingConfig)
                                 (Description ""
                                  :> (Summary "Get config for conferenceCalling"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("conferenceCalling"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          ConferenceCallingConfig))))))))))
                               :<|> (Named
                                       '("iput", ConferenceCallingConfig)
                                       (Description ""
                                        :> (Summary "Put config for conferenceCalling"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("conferenceCalling"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         ConferenceCallingConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            ConferenceCallingConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", ConferenceCallingConfig)
                                            (Description ""
                                             :> (Summary "Patch config for conferenceCalling"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("conferenceCalling"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              ConferenceCallingConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 ConferenceCallingConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", SelfDeletingMessagesConfig)
                                       (Description ""
                                        :> (Summary "Get config for selfDeletingMessages"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("selfDeletingMessages"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                SelfDeletingMessagesConfig))))))))))
                                     :<|> (Named
                                             '("iput", SelfDeletingMessagesConfig)
                                             (Description ""
                                              :> (Summary "Put config for selfDeletingMessages"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("selfDeletingMessages"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               SelfDeletingMessagesConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  SelfDeletingMessagesConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", SelfDeletingMessagesConfig)
                                                  (Description ""
                                                   :> (Summary
                                                         "Patch config for selfDeletingMessages"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("selfDeletingMessages"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    SelfDeletingMessagesConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       SelfDeletingMessagesConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", GuestLinksConfig)
                                             (Description ""
                                              :> (Summary "Get config for conversationGuestLinks"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("conversationGuestLinks"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      GuestLinksConfig))))))))))
                                           :<|> (Named
                                                   '("iput", GuestLinksConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Put config for conversationGuestLinks"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("conversationGuestLinks"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     GuestLinksConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        GuestLinksConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", GuestLinksConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Patch config for conversationGuestLinks"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("conversationGuestLinks"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          GuestLinksConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             GuestLinksConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", SndFactorPasswordChallengeConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Get config for sndFactorPasswordChallenge"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("sndFactorPasswordChallenge"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            SndFactorPasswordChallengeConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", SndFactorPasswordChallengeConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Put config for sndFactorPasswordChallenge"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("sndFactorPasswordChallenge"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           SndFactorPasswordChallengeConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              SndFactorPasswordChallengeConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch",
                                                                SndFactorPasswordChallengeConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for sndFactorPasswordChallenge"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   SndFactorPasswordChallengeConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget", MLSConfig)
                                                         (Description ""
                                                          :> (Summary "Get config for mls"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("mls"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  MLSConfig))))))))))
                                                       :<|> (Named
                                                               '("iput", MLSConfig)
                                                               (Description ""
                                                                :> (Summary "Put config for mls"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mls"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 MLSConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    MLSConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch", MLSConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for mls"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("mls"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      MLSConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         MLSConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget",
                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Get config for exposeInvitationURLsToTeamAdmin"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput",
                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for exposeInvitationURLsToTeamAdmin"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget",
                                                                       OutlookCalIntegrationConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Get config for outlookCalIntegration"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("outlookCalIntegration"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              OutlookCalIntegrationConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput",
                                                                             OutlookCalIntegrationConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Put config for outlookCalIntegration"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("outlookCalIntegration"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             OutlookCalIntegrationConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                OutlookCalIntegrationConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  OutlookCalIntegrationConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Patch config for outlookCalIntegration"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("outlookCalIntegration"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  OutlookCalIntegrationConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     OutlookCalIntegrationConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("iget", MlsE2EIdConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Get config for mlsE2EId"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("mlsE2EId"
                                                                                                            :> Get
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    MlsE2EIdConfig))))))))))
                                                                         :<|> (Named
                                                                                 '("iput",
                                                                                   MlsE2EIdConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Put config for mlsE2EId"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mlsE2EId"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (Feature
                                                                                                                                   MlsE2EIdConfig)
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      MlsE2EIdConfig)))))))))))))
                                                                               :<|> Named
                                                                                      '("ipatch",
                                                                                        MlsE2EIdConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Patch config for mlsE2EId"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("mlsE2EId"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeaturePatch
                                                                                                                                        MlsE2EIdConfig)
                                                                                                                                   :> Patch
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           MlsE2EIdConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("iget",
                                                                                   MlsMigrationConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Get config for mlsMigration"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("mlsMigration"
                                                                                                                  :> Get
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          MlsMigrationConfig))))))))))
                                                                               :<|> (Named
                                                                                       '("iput",
                                                                                         MlsMigrationConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Put config for mlsMigration"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> (CanThrow
                                                                                                              TeamFeatureError
                                                                                                            :> (CanThrowMany
                                                                                                                  '[]
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mlsMigration"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      (Feature
                                                                                                                                         MlsMigrationConfig)
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            MlsMigrationConfig)))))))))))))
                                                                                     :<|> Named
                                                                                            '("ipatch",
                                                                                              MlsMigrationConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (Summary
                                                                                                   "Patch config for mlsMigration"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   TeamFeatureError
                                                                                                                 :> (CanThrowMany
                                                                                                                       '[]
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("mlsMigration"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeaturePatch
                                                                                                                                              MlsMigrationConfig)
                                                                                                                                         :> Patch
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 MlsMigrationConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("iget",
                                                                                         EnforceFileDownloadLocationConfig)
                                                                                       (Description
                                                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                        :> (Summary
                                                                                              "Get config for enforceFileDownloadLocation"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                                        :> Get
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                EnforceFileDownloadLocationConfig))))))))))
                                                                                     :<|> (Named
                                                                                             '("iput",
                                                                                               EnforceFileDownloadLocationConfig)
                                                                                             (Description
                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                              :> (Summary
                                                                                                    "Put config for enforceFileDownloadLocation"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> (CanThrow
                                                                                                                    TeamFeatureError
                                                                                                                  :> (CanThrowMany
                                                                                                                        '[]
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                      :> (ReqBody
                                                                                                                                            '[JSON]
                                                                                                                                            (Feature
                                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                                          :> Put
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  EnforceFileDownloadLocationConfig)))))))))))))
                                                                                           :<|> Named
                                                                                                  '("ipatch",
                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                  (Description
                                                                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                   :> (Summary
                                                                                                         "Patch config for enforceFileDownloadLocation"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         TeamFeatureError
                                                                                                                       :> (CanThrowMany
                                                                                                                             '[]
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("enforceFileDownloadLocation"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                                               :> Patch
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                    :<|> (Named
                                                                                            '("iget",
                                                                                              LimitedEventFanoutConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (Summary
                                                                                                   "Get config for limitedEventFanout"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("limitedEventFanout"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     LimitedEventFanoutConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("iput",
                                                                                                    LimitedEventFanoutConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (Summary
                                                                                                         "Put config for limitedEventFanout"
                                                                                                       :> (CanThrow
                                                                                                             ('MissingPermission
                                                                                                                'Nothing)
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         TeamFeatureError
                                                                                                                       :> (CanThrowMany
                                                                                                                             '[]
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("limitedEventFanout"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 (Feature
                                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                               :> Put
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       LimitedEventFanoutConfig)))))))))))))
                                                                                                :<|> Named
                                                                                                       '("ipatch",
                                                                                                         LimitedEventFanoutConfig)
                                                                                                       (Description
                                                                                                          ""
                                                                                                        :> (Summary
                                                                                                              "Patch config for limitedEventFanout"
                                                                                                            :> (CanThrow
                                                                                                                  ('MissingPermission
                                                                                                                     'Nothing)
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          'TeamNotFound
                                                                                                                        :> (CanThrow
                                                                                                                              TeamFeatureError
                                                                                                                            :> (CanThrowMany
                                                                                                                                  '[]
                                                                                                                                :> ("teams"
                                                                                                                                    :> (Capture
                                                                                                                                          "tid"
                                                                                                                                          TeamId
                                                                                                                                        :> ("features"
                                                                                                                                            :> ("limitedEventFanout"
                                                                                                                                                :> (ReqBody
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeaturePatch
                                                                                                                                                         LimitedEventFanoutConfig)
                                                                                                                                                    :> Patch
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeature
                                                                                                                                                            LimitedEventFanoutConfig)))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", AppLockConfig)
     (Description ""
      :> (Summary "Get config for appLock"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("appLock"
                                      :> Get '[JSON] (LockableFeature AppLockConfig))))))))))
   :<|> (Named
           '("iput", AppLockConfig)
           (Description ""
            :> (Summary "Put config for appLock"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("appLock"
                                                    :> (ReqBody '[JSON] (Feature AppLockConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                AppLockConfig)))))))))))))
         :<|> Named
                '("ipatch", AppLockConfig)
                (Description ""
                 :> (Summary "Patch config for appLock"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("appLock"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch AppLockConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     AppLockConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", AppLockConfig)
     (Description (FeatureAPIDesc AppLockConfig)
      :> (Summary
            (AppendSymbol "Get config for " (FeatureSymbol AppLockConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol AppLockConfig
                                      :> Get '[JSON] (LockableFeature AppLockConfig))))))))))
   :<|> (Named
           '("iput", AppLockConfig)
           (Description (FeatureAPIDesc AppLockConfig)
            :> (Summary
                  (AppendSymbol "Put config for " (FeatureSymbol AppLockConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors AppLockConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol AppLockConfig
                                                    :> (ReqBody '[JSON] (Feature AppLockConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                AppLockConfig)))))))))))))
         :<|> Named
                '("ipatch", AppLockConfig)
                (Description (FeatureAPIDesc AppLockConfig)
                 :> (Summary
                       (AppendSymbol "Patch config for " (FeatureSymbol AppLockConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany (FeatureErrors AppLockConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol AppLockConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch AppLockConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     AppLockConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", AppLockConfig)
     (Description ""
      :> (Summary "Get config for appLock"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("appLock"
                                      :> Get '[JSON] (LockableFeature AppLockConfig))))))))))
   :<|> (Named
           '("iput", AppLockConfig)
           (Description ""
            :> (Summary "Put config for appLock"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("appLock"
                                                    :> (ReqBody '[JSON] (Feature AppLockConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                AppLockConfig)))))))))))))
         :<|> Named
                '("ipatch", AppLockConfig)
                (Description ""
                 :> (Summary "Patch config for appLock"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("appLock"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch AppLockConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     AppLockConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", FileSharingConfig)
         (Description ""
          :> (Summary "Get config for fileSharing"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("fileSharing"
                                          :> Get
                                               '[JSON] (LockableFeature FileSharingConfig))))))))))
       :<|> (Named
               '("iput", FileSharingConfig)
               (Description ""
                :> (Summary "Put config for fileSharing"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("fileSharing"
                                                        :> (ReqBody
                                                              '[JSON] (Feature FileSharingConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    FileSharingConfig)))))))))))))
             :<|> Named
                    '("ipatch", FileSharingConfig)
                    (Description ""
                     :> (Summary "Patch config for fileSharing"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("fileSharing"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      FileSharingConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         FileSharingConfig)))))))))))))))
      :<|> (Named
              '("iget", ClassifiedDomainsConfig)
              (Description ""
               :> (Summary "Get config for classifiedDomains"
                   :> (CanThrow ('MissingPermission 'Nothing)
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> ("teams"
                                   :> (Capture "tid" TeamId
                                       :> ("features"
                                           :> ("classifiedDomains"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       ClassifiedDomainsConfig))))))))))
            :<|> ((Named
                     '("iget", ConferenceCallingConfig)
                     (Description ""
                      :> (Summary "Get config for conferenceCalling"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("conferenceCalling"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              ConferenceCallingConfig))))))))))
                   :<|> (Named
                           '("iput", ConferenceCallingConfig)
                           (Description ""
                            :> (Summary "Put config for conferenceCalling"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("conferenceCalling"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             ConferenceCallingConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                ConferenceCallingConfig)))))))))))))
                         :<|> Named
                                '("ipatch", ConferenceCallingConfig)
                                (Description ""
                                 :> (Summary "Patch config for conferenceCalling"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("conferenceCalling"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  ConferenceCallingConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     ConferenceCallingConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", SelfDeletingMessagesConfig)
                           (Description ""
                            :> (Summary "Get config for selfDeletingMessages"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("selfDeletingMessages"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SelfDeletingMessagesConfig))))))))))
                         :<|> (Named
                                 '("iput", SelfDeletingMessagesConfig)
                                 (Description ""
                                  :> (Summary "Put config for selfDeletingMessages"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("selfDeletingMessages"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   SelfDeletingMessagesConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      SelfDeletingMessagesConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", SelfDeletingMessagesConfig)
                                      (Description ""
                                       :> (Summary "Patch config for selfDeletingMessages"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("selfDeletingMessages"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        SelfDeletingMessagesConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           SelfDeletingMessagesConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", GuestLinksConfig)
                                 (Description ""
                                  :> (Summary "Get config for conversationGuestLinks"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("conversationGuestLinks"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          GuestLinksConfig))))))))))
                               :<|> (Named
                                       '("iput", GuestLinksConfig)
                                       (Description ""
                                        :> (Summary "Put config for conversationGuestLinks"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("conversationGuestLinks"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         GuestLinksConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            GuestLinksConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", GuestLinksConfig)
                                            (Description ""
                                             :> (Summary "Patch config for conversationGuestLinks"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("conversationGuestLinks"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              GuestLinksConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 GuestLinksConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", SndFactorPasswordChallengeConfig)
                                       (Description ""
                                        :> (Summary "Get config for sndFactorPasswordChallenge"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("sndFactorPasswordChallenge"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                SndFactorPasswordChallengeConfig))))))))))
                                     :<|> (Named
                                             '("iput", SndFactorPasswordChallengeConfig)
                                             (Description ""
                                              :> (Summary
                                                    "Put config for sndFactorPasswordChallenge"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("sndFactorPasswordChallenge"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               SndFactorPasswordChallengeConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  SndFactorPasswordChallengeConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", SndFactorPasswordChallengeConfig)
                                                  (Description ""
                                                   :> (Summary
                                                         "Patch config for sndFactorPasswordChallenge"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    SndFactorPasswordChallengeConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       SndFactorPasswordChallengeConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", MLSConfig)
                                             (Description ""
                                              :> (Summary "Get config for mls"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("mls"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      MLSConfig))))))))))
                                           :<|> (Named
                                                   '("iput", MLSConfig)
                                                   (Description ""
                                                    :> (Summary "Put config for mls"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mls"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     MLSConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        MLSConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", MLSConfig)
                                                        (Description ""
                                                         :> (Summary "Patch config for mls"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("mls"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          MLSConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             MLSConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", ExposeInvitationURLsToTeamAdminConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Get config for exposeInvitationURLsToTeamAdmin"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                 :<|> (Named
                                                         '("iput",
                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Put config for exposeInvitationURLsToTeamAdmin"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch",
                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget", OutlookCalIntegrationConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Get config for outlookCalIntegration"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("outlookCalIntegration"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  OutlookCalIntegrationConfig))))))))))
                                                       :<|> (Named
                                                               '("iput",
                                                                 OutlookCalIntegrationConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for outlookCalIntegration"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("outlookCalIntegration"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 OutlookCalIntegrationConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    OutlookCalIntegrationConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch",
                                                                      OutlookCalIntegrationConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for outlookCalIntegration"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("outlookCalIntegration"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      OutlookCalIntegrationConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         OutlookCalIntegrationConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget", MlsE2EIdConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Get config for mlsE2EId"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("mlsE2EId"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        MlsE2EIdConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput", MlsE2EIdConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for mlsE2EId"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mlsE2EId"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       MlsE2EIdConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          MlsE2EIdConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            MlsE2EIdConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for mlsE2EId"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("mlsE2EId"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            MlsE2EIdConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               MlsE2EIdConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget", MlsMigrationConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Get config for mlsMigration"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("mlsMigration"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              MlsMigrationConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput",
                                                                             MlsMigrationConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Put config for mlsMigration"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mlsMigration"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             MlsMigrationConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                MlsMigrationConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  MlsMigrationConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Patch config for mlsMigration"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("mlsMigration"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  MlsMigrationConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     MlsMigrationConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("iget",
                                                                             EnforceFileDownloadLocationConfig)
                                                                           (Description
                                                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                            :> (Summary
                                                                                  "Get config for enforceFileDownloadLocation"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("enforceFileDownloadLocation"
                                                                                                            :> Get
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    EnforceFileDownloadLocationConfig))))))))))
                                                                         :<|> (Named
                                                                                 '("iput",
                                                                                   EnforceFileDownloadLocationConfig)
                                                                                 (Description
                                                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                  :> (Summary
                                                                                        "Put config for enforceFileDownloadLocation"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("enforceFileDownloadLocation"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (Feature
                                                                                                                                   EnforceFileDownloadLocationConfig)
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      EnforceFileDownloadLocationConfig)))))))))))))
                                                                               :<|> Named
                                                                                      '("ipatch",
                                                                                        EnforceFileDownloadLocationConfig)
                                                                                      (Description
                                                                                         "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                       :> (Summary
                                                                                             "Patch config for enforceFileDownloadLocation"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("enforceFileDownloadLocation"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeaturePatch
                                                                                                                                        EnforceFileDownloadLocationConfig)
                                                                                                                                   :> Patch
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           EnforceFileDownloadLocationConfig)))))))))))))))
                                                                        :<|> (Named
                                                                                '("iget",
                                                                                  LimitedEventFanoutConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Get config for limitedEventFanout"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("limitedEventFanout"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         LimitedEventFanoutConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("iput",
                                                                                        LimitedEventFanoutConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Put config for limitedEventFanout"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("limitedEventFanout"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (Feature
                                                                                                                                        LimitedEventFanoutConfig)
                                                                                                                                   :> Put
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           LimitedEventFanoutConfig)))))))))))))
                                                                                    :<|> Named
                                                                                           '("ipatch",
                                                                                             LimitedEventFanoutConfig)
                                                                                           (Description
                                                                                              ""
                                                                                            :> (Summary
                                                                                                  "Patch config for limitedEventFanout"
                                                                                                :> (CanThrow
                                                                                                      ('MissingPermission
                                                                                                         'Nothing)
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> (CanThrow
                                                                                                                  TeamFeatureError
                                                                                                                :> (CanThrowMany
                                                                                                                      '[]
                                                                                                                    :> ("teams"
                                                                                                                        :> (Capture
                                                                                                                              "tid"
                                                                                                                              TeamId
                                                                                                                            :> ("features"
                                                                                                                                :> ("limitedEventFanout"
                                                                                                                                    :> (ReqBody
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeaturePatch
                                                                                                                                             LimitedEventFanoutConfig)
                                                                                                                                        :> Patch
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeature
                                                                                                                                                LimitedEventFanoutConfig)))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", AppLockConfig)
         (Description ""
          :> (Summary "Get config for appLock"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("appLock"
                                          :> Get '[JSON] (LockableFeature AppLockConfig))))))))))
       :<|> (Named
               '("iput", AppLockConfig)
               (Description ""
                :> (Summary "Put config for appLock"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("appLock"
                                                        :> (ReqBody '[JSON] (Feature AppLockConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    AppLockConfig)))))))))))))
             :<|> Named
                    '("ipatch", AppLockConfig)
                    (Description ""
                     :> (Summary "Patch config for appLock"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("appLock"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      AppLockConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         AppLockConfig)))))))))))))))
      :<|> ((Named
               '("iget", FileSharingConfig)
               (Description ""
                :> (Summary "Get config for fileSharing"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("fileSharing"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature FileSharingConfig))))))))))
             :<|> (Named
                     '("iput", FileSharingConfig)
                     (Description ""
                      :> (Summary "Put config for fileSharing"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("fileSharing"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature FileSharingConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          FileSharingConfig)))))))))))))
                   :<|> Named
                          '("ipatch", FileSharingConfig)
                          (Description ""
                           :> (Summary "Patch config for fileSharing"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("fileSharing"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            FileSharingConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               FileSharingConfig)))))))))))))))
            :<|> (Named
                    '("iget", ClassifiedDomainsConfig)
                    (Description ""
                     :> (Summary "Get config for classifiedDomains"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> ("teams"
                                         :> (Capture "tid" TeamId
                                             :> ("features"
                                                 :> ("classifiedDomains"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             ClassifiedDomainsConfig))))))))))
                  :<|> ((Named
                           '("iget", ConferenceCallingConfig)
                           (Description ""
                            :> (Summary "Get config for conferenceCalling"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("conferenceCalling"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    ConferenceCallingConfig))))))))))
                         :<|> (Named
                                 '("iput", ConferenceCallingConfig)
                                 (Description ""
                                  :> (Summary "Put config for conferenceCalling"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("conferenceCalling"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   ConferenceCallingConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      ConferenceCallingConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", ConferenceCallingConfig)
                                      (Description ""
                                       :> (Summary "Patch config for conferenceCalling"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("conferenceCalling"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        ConferenceCallingConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           ConferenceCallingConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", SelfDeletingMessagesConfig)
                                 (Description ""
                                  :> (Summary "Get config for selfDeletingMessages"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("selfDeletingMessages"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          SelfDeletingMessagesConfig))))))))))
                               :<|> (Named
                                       '("iput", SelfDeletingMessagesConfig)
                                       (Description ""
                                        :> (Summary "Put config for selfDeletingMessages"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("selfDeletingMessages"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         SelfDeletingMessagesConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            SelfDeletingMessagesConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", SelfDeletingMessagesConfig)
                                            (Description ""
                                             :> (Summary "Patch config for selfDeletingMessages"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("selfDeletingMessages"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              SelfDeletingMessagesConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 SelfDeletingMessagesConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", GuestLinksConfig)
                                       (Description ""
                                        :> (Summary "Get config for conversationGuestLinks"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("conversationGuestLinks"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                GuestLinksConfig))))))))))
                                     :<|> (Named
                                             '("iput", GuestLinksConfig)
                                             (Description ""
                                              :> (Summary "Put config for conversationGuestLinks"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("conversationGuestLinks"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               GuestLinksConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  GuestLinksConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", GuestLinksConfig)
                                                  (Description ""
                                                   :> (Summary
                                                         "Patch config for conversationGuestLinks"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("conversationGuestLinks"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    GuestLinksConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       GuestLinksConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", SndFactorPasswordChallengeConfig)
                                             (Description ""
                                              :> (Summary
                                                    "Get config for sndFactorPasswordChallenge"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("sndFactorPasswordChallenge"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      SndFactorPasswordChallengeConfig))))))))))
                                           :<|> (Named
                                                   '("iput", SndFactorPasswordChallengeConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Put config for sndFactorPasswordChallenge"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("sndFactorPasswordChallenge"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     SndFactorPasswordChallengeConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        SndFactorPasswordChallengeConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch",
                                                          SndFactorPasswordChallengeConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Patch config for sndFactorPasswordChallenge"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("sndFactorPasswordChallenge"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          SndFactorPasswordChallengeConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             SndFactorPasswordChallengeConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", MLSConfig)
                                                   (Description ""
                                                    :> (Summary "Get config for mls"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("mls"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            MLSConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", MLSConfig)
                                                         (Description ""
                                                          :> (Summary "Put config for mls"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mls"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           MLSConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              MLSConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch", MLSConfig)
                                                              (Description ""
                                                               :> (Summary "Patch config for mls"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("mls"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                MLSConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   MLSConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget",
                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Get config for exposeInvitationURLsToTeamAdmin"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                       :<|> (Named
                                                               '("iput",
                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for exposeInvitationURLsToTeamAdmin"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch",
                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget",
                                                                 OutlookCalIntegrationConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Get config for outlookCalIntegration"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("outlookCalIntegration"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        OutlookCalIntegrationConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput",
                                                                       OutlookCalIntegrationConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for outlookCalIntegration"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("outlookCalIntegration"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       OutlookCalIntegrationConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          OutlookCalIntegrationConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            OutlookCalIntegrationConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for outlookCalIntegration"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("outlookCalIntegration"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            OutlookCalIntegrationConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               OutlookCalIntegrationConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget", MlsE2EIdConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Get config for mlsE2EId"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("mlsE2EId"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              MlsE2EIdConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput", MlsE2EIdConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Put config for mlsE2EId"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mlsE2EId"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             MlsE2EIdConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                MlsE2EIdConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  MlsE2EIdConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Patch config for mlsE2EId"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("mlsE2EId"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  MlsE2EIdConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     MlsE2EIdConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("iget",
                                                                             MlsMigrationConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Get config for mlsMigration"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("mlsMigration"
                                                                                                            :> Get
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    MlsMigrationConfig))))))))))
                                                                         :<|> (Named
                                                                                 '("iput",
                                                                                   MlsMigrationConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Put config for mlsMigration"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mlsMigration"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (Feature
                                                                                                                                   MlsMigrationConfig)
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      MlsMigrationConfig)))))))))))))
                                                                               :<|> Named
                                                                                      '("ipatch",
                                                                                        MlsMigrationConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Patch config for mlsMigration"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("mlsMigration"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeaturePatch
                                                                                                                                        MlsMigrationConfig)
                                                                                                                                   :> Patch
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           MlsMigrationConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("iget",
                                                                                   EnforceFileDownloadLocationConfig)
                                                                                 (Description
                                                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                  :> (Summary
                                                                                        "Get config for enforceFileDownloadLocation"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                                  :> Get
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          EnforceFileDownloadLocationConfig))))))))))
                                                                               :<|> (Named
                                                                                       '("iput",
                                                                                         EnforceFileDownloadLocationConfig)
                                                                                       (Description
                                                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                        :> (Summary
                                                                                              "Put config for enforceFileDownloadLocation"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> (CanThrow
                                                                                                              TeamFeatureError
                                                                                                            :> (CanThrowMany
                                                                                                                  '[]
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      (Feature
                                                                                                                                         EnforceFileDownloadLocationConfig)
                                                                                                                                    :> Put
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            EnforceFileDownloadLocationConfig)))))))))))))
                                                                                     :<|> Named
                                                                                            '("ipatch",
                                                                                              EnforceFileDownloadLocationConfig)
                                                                                            (Description
                                                                                               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                             :> (Summary
                                                                                                   "Patch config for enforceFileDownloadLocation"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   TeamFeatureError
                                                                                                                 :> (CanThrowMany
                                                                                                                       '[]
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("enforceFileDownloadLocation"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeaturePatch
                                                                                                                                              EnforceFileDownloadLocationConfig)
                                                                                                                                         :> Patch
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 EnforceFileDownloadLocationConfig)))))))))))))))
                                                                              :<|> (Named
                                                                                      '("iget",
                                                                                        LimitedEventFanoutConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Get config for limitedEventFanout"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("limitedEventFanout"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               LimitedEventFanoutConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("iput",
                                                                                              LimitedEventFanoutConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (Summary
                                                                                                   "Put config for limitedEventFanout"
                                                                                                 :> (CanThrow
                                                                                                       ('MissingPermission
                                                                                                          'Nothing)
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   TeamFeatureError
                                                                                                                 :> (CanThrowMany
                                                                                                                       '[]
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("limitedEventFanout"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           (Feature
                                                                                                                                              LimitedEventFanoutConfig)
                                                                                                                                         :> Put
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 LimitedEventFanoutConfig)))))))))))))
                                                                                          :<|> Named
                                                                                                 '("ipatch",
                                                                                                   LimitedEventFanoutConfig)
                                                                                                 (Description
                                                                                                    ""
                                                                                                  :> (Summary
                                                                                                        "Patch config for limitedEventFanout"
                                                                                                      :> (CanThrow
                                                                                                            ('MissingPermission
                                                                                                               'Nothing)
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> (CanThrow
                                                                                                                        TeamFeatureError
                                                                                                                      :> (CanThrowMany
                                                                                                                            '[]
                                                                                                                          :> ("teams"
                                                                                                                              :> (Capture
                                                                                                                                    "tid"
                                                                                                                                    TeamId
                                                                                                                                  :> ("features"
                                                                                                                                      :> ("limitedEventFanout"
                                                                                                                                          :> (ReqBody
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeaturePatch
                                                                                                                                                   LimitedEventFanoutConfig)
                                                                                                                                              :> Patch
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeature
                                                                                                                                                      LimitedEventFanoutConfig))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", FileSharingConfig)
     (Description ""
      :> (Summary "Get config for fileSharing"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("fileSharing"
                                      :> Get '[JSON] (LockableFeature FileSharingConfig))))))))))
   :<|> (Named
           '("iput", FileSharingConfig)
           (Description ""
            :> (Summary "Put config for fileSharing"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("fileSharing"
                                                    :> (ReqBody '[JSON] (Feature FileSharingConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                FileSharingConfig)))))))))))))
         :<|> Named
                '("ipatch", FileSharingConfig)
                (Description ""
                 :> (Summary "Patch config for fileSharing"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("fileSharing"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  FileSharingConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     FileSharingConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", FileSharingConfig)
     (Description (FeatureAPIDesc FileSharingConfig)
      :> (Summary
            (AppendSymbol "Get config for " (FeatureSymbol FileSharingConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol FileSharingConfig
                                      :> Get '[JSON] (LockableFeature FileSharingConfig))))))))))
   :<|> (Named
           '("iput", FileSharingConfig)
           (Description (FeatureAPIDesc FileSharingConfig)
            :> (Summary
                  (AppendSymbol "Put config for " (FeatureSymbol FileSharingConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors FileSharingConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol FileSharingConfig
                                                    :> (ReqBody '[JSON] (Feature FileSharingConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                FileSharingConfig)))))))))))))
         :<|> Named
                '("ipatch", FileSharingConfig)
                (Description (FeatureAPIDesc FileSharingConfig)
                 :> (Summary
                       (AppendSymbol
                          "Patch config for " (FeatureSymbol FileSharingConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany (FeatureErrors FileSharingConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol FileSharingConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  FileSharingConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     FileSharingConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", FileSharingConfig)
     (Description ""
      :> (Summary "Get config for fileSharing"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("fileSharing"
                                      :> Get '[JSON] (LockableFeature FileSharingConfig))))))))))
   :<|> (Named
           '("iput", FileSharingConfig)
           (Description ""
            :> (Summary "Put config for fileSharing"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("fileSharing"
                                                    :> (ReqBody '[JSON] (Feature FileSharingConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                FileSharingConfig)))))))))))))
         :<|> Named
                '("ipatch", FileSharingConfig)
                (Description ""
                 :> (Summary "Patch config for fileSharing"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("fileSharing"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  FileSharingConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     FileSharingConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        '("iget", ClassifiedDomainsConfig)
        (Description ""
         :> (Summary "Get config for classifiedDomains"
             :> (CanThrow ('MissingPermission 'Nothing)
                 :> (CanThrow 'NotATeamMember
                     :> (CanThrow 'TeamNotFound
                         :> ("teams"
                             :> (Capture "tid" TeamId
                                 :> ("features"
                                     :> ("classifiedDomains"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature ClassifiedDomainsConfig))))))))))
      :<|> ((Named
               '("iget", ConferenceCallingConfig)
               (Description ""
                :> (Summary "Get config for conferenceCalling"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("conferenceCalling"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        ConferenceCallingConfig))))))))))
             :<|> (Named
                     '("iput", ConferenceCallingConfig)
                     (Description ""
                      :> (Summary "Put config for conferenceCalling"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("conferenceCalling"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       ConferenceCallingConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          ConferenceCallingConfig)))))))))))))
                   :<|> Named
                          '("ipatch", ConferenceCallingConfig)
                          (Description ""
                           :> (Summary "Patch config for conferenceCalling"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("conferenceCalling"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            ConferenceCallingConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               ConferenceCallingConfig)))))))))))))))
            :<|> ((Named
                     '("iget", SelfDeletingMessagesConfig)
                     (Description ""
                      :> (Summary "Get config for selfDeletingMessages"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("selfDeletingMessages"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              SelfDeletingMessagesConfig))))))))))
                   :<|> (Named
                           '("iput", SelfDeletingMessagesConfig)
                           (Description ""
                            :> (Summary "Put config for selfDeletingMessages"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("selfDeletingMessages"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             SelfDeletingMessagesConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                SelfDeletingMessagesConfig)))))))))))))
                         :<|> Named
                                '("ipatch", SelfDeletingMessagesConfig)
                                (Description ""
                                 :> (Summary "Patch config for selfDeletingMessages"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("selfDeletingMessages"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  SelfDeletingMessagesConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     SelfDeletingMessagesConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", GuestLinksConfig)
                           (Description ""
                            :> (Summary "Get config for conversationGuestLinks"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("conversationGuestLinks"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    GuestLinksConfig))))))))))
                         :<|> (Named
                                 '("iput", GuestLinksConfig)
                                 (Description ""
                                  :> (Summary "Put config for conversationGuestLinks"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("conversationGuestLinks"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   GuestLinksConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      GuestLinksConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", GuestLinksConfig)
                                      (Description ""
                                       :> (Summary "Patch config for conversationGuestLinks"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("conversationGuestLinks"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        GuestLinksConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           GuestLinksConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", SndFactorPasswordChallengeConfig)
                                 (Description ""
                                  :> (Summary "Get config for sndFactorPasswordChallenge"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("sndFactorPasswordChallenge"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          SndFactorPasswordChallengeConfig))))))))))
                               :<|> (Named
                                       '("iput", SndFactorPasswordChallengeConfig)
                                       (Description ""
                                        :> (Summary "Put config for sndFactorPasswordChallenge"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("sndFactorPasswordChallenge"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         SndFactorPasswordChallengeConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            SndFactorPasswordChallengeConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", SndFactorPasswordChallengeConfig)
                                            (Description ""
                                             :> (Summary
                                                   "Patch config for sndFactorPasswordChallenge"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("sndFactorPasswordChallenge"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              SndFactorPasswordChallengeConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 SndFactorPasswordChallengeConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", MLSConfig)
                                       (Description ""
                                        :> (Summary "Get config for mls"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("mls"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                MLSConfig))))))))))
                                     :<|> (Named
                                             '("iput", MLSConfig)
                                             (Description ""
                                              :> (Summary "Put config for mls"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("mls"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               MLSConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  MLSConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", MLSConfig)
                                                  (Description ""
                                                   :> (Summary "Patch config for mls"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("mls"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    MLSConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       MLSConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", ExposeInvitationURLsToTeamAdminConfig)
                                             (Description ""
                                              :> (Summary
                                                    "Get config for exposeInvitationURLsToTeamAdmin"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      ExposeInvitationURLsToTeamAdminConfig))))))))))
                                           :<|> (Named
                                                   '("iput", ExposeInvitationURLsToTeamAdminConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Put config for exposeInvitationURLsToTeamAdmin"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     ExposeInvitationURLsToTeamAdminConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch",
                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Patch config for exposeInvitationURLsToTeamAdmin"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", OutlookCalIntegrationConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Get config for outlookCalIntegration"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("outlookCalIntegration"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            OutlookCalIntegrationConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", OutlookCalIntegrationConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Put config for outlookCalIntegration"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("outlookCalIntegration"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           OutlookCalIntegrationConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              OutlookCalIntegrationConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch",
                                                                OutlookCalIntegrationConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for outlookCalIntegration"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("outlookCalIntegration"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                OutlookCalIntegrationConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   OutlookCalIntegrationConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget", MlsE2EIdConfig)
                                                         (Description ""
                                                          :> (Summary "Get config for mlsE2EId"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("mlsE2EId"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  MlsE2EIdConfig))))))))))
                                                       :<|> (Named
                                                               '("iput", MlsE2EIdConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for mlsE2EId"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mlsE2EId"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 MlsE2EIdConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    MlsE2EIdConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch", MlsE2EIdConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for mlsE2EId"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("mlsE2EId"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      MlsE2EIdConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         MlsE2EIdConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget", MlsMigrationConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Get config for mlsMigration"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("mlsMigration"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        MlsMigrationConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput", MlsMigrationConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for mlsMigration"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mlsMigration"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       MlsMigrationConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          MlsMigrationConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            MlsMigrationConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for mlsMigration"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("mlsMigration"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            MlsMigrationConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               MlsMigrationConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget",
                                                                       EnforceFileDownloadLocationConfig)
                                                                     (Description
                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                      :> (Summary
                                                                            "Get config for enforceFileDownloadLocation"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              EnforceFileDownloadLocationConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput",
                                                                             EnforceFileDownloadLocationConfig)
                                                                           (Description
                                                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                            :> (Summary
                                                                                  "Put config for enforceFileDownloadLocation"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             EnforceFileDownloadLocationConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                EnforceFileDownloadLocationConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  EnforceFileDownloadLocationConfig)
                                                                                (Description
                                                                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                 :> (Summary
                                                                                       "Patch config for enforceFileDownloadLocation"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("enforceFileDownloadLocation"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  EnforceFileDownloadLocationConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     EnforceFileDownloadLocationConfig)))))))))))))))
                                                                  :<|> (Named
                                                                          '("iget",
                                                                            LimitedEventFanoutConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Get config for limitedEventFanout"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("limitedEventFanout"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   LimitedEventFanoutConfig))))))))))
                                                                        :<|> (Named
                                                                                '("iput",
                                                                                  LimitedEventFanoutConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Put config for limitedEventFanout"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("limitedEventFanout"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (Feature
                                                                                                                                  LimitedEventFanoutConfig)
                                                                                                                             :> Put
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     LimitedEventFanoutConfig)))))))))))))
                                                                              :<|> Named
                                                                                     '("ipatch",
                                                                                       LimitedEventFanoutConfig)
                                                                                     (Description ""
                                                                                      :> (Summary
                                                                                            "Patch config for limitedEventFanout"
                                                                                          :> (CanThrow
                                                                                                ('MissingPermission
                                                                                                   'Nothing)
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> (CanThrow
                                                                                                            TeamFeatureError
                                                                                                          :> (CanThrowMany
                                                                                                                '[]
                                                                                                              :> ("teams"
                                                                                                                  :> (Capture
                                                                                                                        "tid"
                                                                                                                        TeamId
                                                                                                                      :> ("features"
                                                                                                                          :> ("limitedEventFanout"
                                                                                                                              :> (ReqBody
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeaturePatch
                                                                                                                                       LimitedEventFanoutConfig)
                                                                                                                                  :> Patch
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeature
                                                                                                                                          LimitedEventFanoutConfig))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", FileSharingConfig)
         (Description ""
          :> (Summary "Get config for fileSharing"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("fileSharing"
                                          :> Get
                                               '[JSON] (LockableFeature FileSharingConfig))))))))))
       :<|> (Named
               '("iput", FileSharingConfig)
               (Description ""
                :> (Summary "Put config for fileSharing"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("fileSharing"
                                                        :> (ReqBody
                                                              '[JSON] (Feature FileSharingConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    FileSharingConfig)))))))))))))
             :<|> Named
                    '("ipatch", FileSharingConfig)
                    (Description ""
                     :> (Summary "Patch config for fileSharing"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("fileSharing"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      FileSharingConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         FileSharingConfig)))))))))))))))
      :<|> (Named
              '("iget", ClassifiedDomainsConfig)
              (Description ""
               :> (Summary "Get config for classifiedDomains"
                   :> (CanThrow ('MissingPermission 'Nothing)
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> ("teams"
                                   :> (Capture "tid" TeamId
                                       :> ("features"
                                           :> ("classifiedDomains"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       ClassifiedDomainsConfig))))))))))
            :<|> ((Named
                     '("iget", ConferenceCallingConfig)
                     (Description ""
                      :> (Summary "Get config for conferenceCalling"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("conferenceCalling"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              ConferenceCallingConfig))))))))))
                   :<|> (Named
                           '("iput", ConferenceCallingConfig)
                           (Description ""
                            :> (Summary "Put config for conferenceCalling"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("conferenceCalling"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             ConferenceCallingConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                ConferenceCallingConfig)))))))))))))
                         :<|> Named
                                '("ipatch", ConferenceCallingConfig)
                                (Description ""
                                 :> (Summary "Patch config for conferenceCalling"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("conferenceCalling"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  ConferenceCallingConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     ConferenceCallingConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", SelfDeletingMessagesConfig)
                           (Description ""
                            :> (Summary "Get config for selfDeletingMessages"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("selfDeletingMessages"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SelfDeletingMessagesConfig))))))))))
                         :<|> (Named
                                 '("iput", SelfDeletingMessagesConfig)
                                 (Description ""
                                  :> (Summary "Put config for selfDeletingMessages"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("selfDeletingMessages"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   SelfDeletingMessagesConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      SelfDeletingMessagesConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", SelfDeletingMessagesConfig)
                                      (Description ""
                                       :> (Summary "Patch config for selfDeletingMessages"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("selfDeletingMessages"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        SelfDeletingMessagesConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           SelfDeletingMessagesConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", GuestLinksConfig)
                                 (Description ""
                                  :> (Summary "Get config for conversationGuestLinks"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("conversationGuestLinks"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          GuestLinksConfig))))))))))
                               :<|> (Named
                                       '("iput", GuestLinksConfig)
                                       (Description ""
                                        :> (Summary "Put config for conversationGuestLinks"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("conversationGuestLinks"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         GuestLinksConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            GuestLinksConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", GuestLinksConfig)
                                            (Description ""
                                             :> (Summary "Patch config for conversationGuestLinks"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("conversationGuestLinks"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              GuestLinksConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 GuestLinksConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", SndFactorPasswordChallengeConfig)
                                       (Description ""
                                        :> (Summary "Get config for sndFactorPasswordChallenge"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("sndFactorPasswordChallenge"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                SndFactorPasswordChallengeConfig))))))))))
                                     :<|> (Named
                                             '("iput", SndFactorPasswordChallengeConfig)
                                             (Description ""
                                              :> (Summary
                                                    "Put config for sndFactorPasswordChallenge"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("sndFactorPasswordChallenge"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               SndFactorPasswordChallengeConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  SndFactorPasswordChallengeConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", SndFactorPasswordChallengeConfig)
                                                  (Description ""
                                                   :> (Summary
                                                         "Patch config for sndFactorPasswordChallenge"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    SndFactorPasswordChallengeConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       SndFactorPasswordChallengeConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", MLSConfig)
                                             (Description ""
                                              :> (Summary "Get config for mls"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("mls"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      MLSConfig))))))))))
                                           :<|> (Named
                                                   '("iput", MLSConfig)
                                                   (Description ""
                                                    :> (Summary "Put config for mls"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mls"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     MLSConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        MLSConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", MLSConfig)
                                                        (Description ""
                                                         :> (Summary "Patch config for mls"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("mls"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          MLSConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             MLSConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", ExposeInvitationURLsToTeamAdminConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Get config for exposeInvitationURLsToTeamAdmin"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                 :<|> (Named
                                                         '("iput",
                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Put config for exposeInvitationURLsToTeamAdmin"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch",
                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget", OutlookCalIntegrationConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Get config for outlookCalIntegration"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("outlookCalIntegration"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  OutlookCalIntegrationConfig))))))))))
                                                       :<|> (Named
                                                               '("iput",
                                                                 OutlookCalIntegrationConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for outlookCalIntegration"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("outlookCalIntegration"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 OutlookCalIntegrationConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    OutlookCalIntegrationConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch",
                                                                      OutlookCalIntegrationConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for outlookCalIntegration"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("outlookCalIntegration"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      OutlookCalIntegrationConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         OutlookCalIntegrationConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget", MlsE2EIdConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Get config for mlsE2EId"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("mlsE2EId"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        MlsE2EIdConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput", MlsE2EIdConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for mlsE2EId"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mlsE2EId"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       MlsE2EIdConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          MlsE2EIdConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            MlsE2EIdConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for mlsE2EId"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("mlsE2EId"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            MlsE2EIdConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               MlsE2EIdConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget", MlsMigrationConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Get config for mlsMigration"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("mlsMigration"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              MlsMigrationConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput",
                                                                             MlsMigrationConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Put config for mlsMigration"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mlsMigration"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             MlsMigrationConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                MlsMigrationConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  MlsMigrationConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Patch config for mlsMigration"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("mlsMigration"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  MlsMigrationConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     MlsMigrationConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("iget",
                                                                             EnforceFileDownloadLocationConfig)
                                                                           (Description
                                                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                            :> (Summary
                                                                                  "Get config for enforceFileDownloadLocation"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("enforceFileDownloadLocation"
                                                                                                            :> Get
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    EnforceFileDownloadLocationConfig))))))))))
                                                                         :<|> (Named
                                                                                 '("iput",
                                                                                   EnforceFileDownloadLocationConfig)
                                                                                 (Description
                                                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                  :> (Summary
                                                                                        "Put config for enforceFileDownloadLocation"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("enforceFileDownloadLocation"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (Feature
                                                                                                                                   EnforceFileDownloadLocationConfig)
                                                                                                                              :> Put
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      EnforceFileDownloadLocationConfig)))))))))))))
                                                                               :<|> Named
                                                                                      '("ipatch",
                                                                                        EnforceFileDownloadLocationConfig)
                                                                                      (Description
                                                                                         "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                       :> (Summary
                                                                                             "Patch config for enforceFileDownloadLocation"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("enforceFileDownloadLocation"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeaturePatch
                                                                                                                                        EnforceFileDownloadLocationConfig)
                                                                                                                                   :> Patch
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           EnforceFileDownloadLocationConfig)))))))))))))))
                                                                        :<|> (Named
                                                                                '("iget",
                                                                                  LimitedEventFanoutConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Get config for limitedEventFanout"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("limitedEventFanout"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         LimitedEventFanoutConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("iput",
                                                                                        LimitedEventFanoutConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (Summary
                                                                                             "Put config for limitedEventFanout"
                                                                                           :> (CanThrow
                                                                                                 ('MissingPermission
                                                                                                    'Nothing)
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             TeamFeatureError
                                                                                                           :> (CanThrowMany
                                                                                                                 '[]
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("limitedEventFanout"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     (Feature
                                                                                                                                        LimitedEventFanoutConfig)
                                                                                                                                   :> Put
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           LimitedEventFanoutConfig)))))))))))))
                                                                                    :<|> Named
                                                                                           '("ipatch",
                                                                                             LimitedEventFanoutConfig)
                                                                                           (Description
                                                                                              ""
                                                                                            :> (Summary
                                                                                                  "Patch config for limitedEventFanout"
                                                                                                :> (CanThrow
                                                                                                      ('MissingPermission
                                                                                                         'Nothing)
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> (CanThrow
                                                                                                                  TeamFeatureError
                                                                                                                :> (CanThrowMany
                                                                                                                      '[]
                                                                                                                    :> ("teams"
                                                                                                                        :> (Capture
                                                                                                                              "tid"
                                                                                                                              TeamId
                                                                                                                            :> ("features"
                                                                                                                                :> ("limitedEventFanout"
                                                                                                                                    :> (ReqBody
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeaturePatch
                                                                                                                                             LimitedEventFanoutConfig)
                                                                                                                                        :> Patch
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeature
                                                                                                                                                LimitedEventFanoutConfig)))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", ClassifiedDomainsConfig)
     (Description ""
      :> (Summary "Get config for classifiedDomains"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("classifiedDomains"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature ClassifiedDomainsConfig)))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", ClassifiedDomainsConfig)
     (Description (FeatureAPIDesc ClassifiedDomainsConfig)
      :> (Summary
            (AppendSymbol
               "Get config for " (FeatureSymbol ClassifiedDomainsConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol ClassifiedDomainsConfig
                                      :> Get
                                           '[JSON]
                                           (LockableFeature ClassifiedDomainsConfig)))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 GetFeatureConfig cfg, Member (Input Opts) r,
 Member (Error DynError) r, Member TeamFeatureStore r,
 Member TeamStore r) =>
API (IFeatureStatusGet cfg) r
featureAPI1Get
    API
  (Named
     '("iget", ClassifiedDomainsConfig)
     (Description ""
      :> (Summary "Get config for classifiedDomains"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("classifiedDomains"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature ClassifiedDomainsConfig)))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", ConferenceCallingConfig)
         (Description ""
          :> (Summary "Get config for conferenceCalling"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("conferenceCalling"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature ConferenceCallingConfig))))))))))
       :<|> (Named
               '("iput", ConferenceCallingConfig)
               (Description ""
                :> (Summary "Put config for conferenceCalling"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("conferenceCalling"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature ConferenceCallingConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    ConferenceCallingConfig)))))))))))))
             :<|> Named
                    '("ipatch", ConferenceCallingConfig)
                    (Description ""
                     :> (Summary "Patch config for conferenceCalling"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("conferenceCalling"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      ConferenceCallingConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         ConferenceCallingConfig)))))))))))))))
      :<|> ((Named
               '("iget", SelfDeletingMessagesConfig)
               (Description ""
                :> (Summary "Get config for selfDeletingMessages"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("selfDeletingMessages"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        SelfDeletingMessagesConfig))))))))))
             :<|> (Named
                     '("iput", SelfDeletingMessagesConfig)
                     (Description ""
                      :> (Summary "Put config for selfDeletingMessages"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("selfDeletingMessages"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       SelfDeletingMessagesConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          SelfDeletingMessagesConfig)))))))))))))
                   :<|> Named
                          '("ipatch", SelfDeletingMessagesConfig)
                          (Description ""
                           :> (Summary "Patch config for selfDeletingMessages"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("selfDeletingMessages"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            SelfDeletingMessagesConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SelfDeletingMessagesConfig)))))))))))))))
            :<|> ((Named
                     '("iget", GuestLinksConfig)
                     (Description ""
                      :> (Summary "Get config for conversationGuestLinks"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("conversationGuestLinks"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              GuestLinksConfig))))))))))
                   :<|> (Named
                           '("iput", GuestLinksConfig)
                           (Description ""
                            :> (Summary "Put config for conversationGuestLinks"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("conversationGuestLinks"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature GuestLinksConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                GuestLinksConfig)))))))))))))
                         :<|> Named
                                '("ipatch", GuestLinksConfig)
                                (Description ""
                                 :> (Summary "Patch config for conversationGuestLinks"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("conversationGuestLinks"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  GuestLinksConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     GuestLinksConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", SndFactorPasswordChallengeConfig)
                           (Description ""
                            :> (Summary "Get config for sndFactorPasswordChallenge"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("sndFactorPasswordChallenge"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SndFactorPasswordChallengeConfig))))))))))
                         :<|> (Named
                                 '("iput", SndFactorPasswordChallengeConfig)
                                 (Description ""
                                  :> (Summary "Put config for sndFactorPasswordChallenge"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("sndFactorPasswordChallenge"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   SndFactorPasswordChallengeConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      SndFactorPasswordChallengeConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", SndFactorPasswordChallengeConfig)
                                      (Description ""
                                       :> (Summary "Patch config for sndFactorPasswordChallenge"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("sndFactorPasswordChallenge"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        SndFactorPasswordChallengeConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           SndFactorPasswordChallengeConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", MLSConfig)
                                 (Description ""
                                  :> (Summary "Get config for mls"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("mls"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          MLSConfig))))))))))
                               :<|> (Named
                                       '("iput", MLSConfig)
                                       (Description ""
                                        :> (Summary "Put config for mls"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("mls"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         MLSConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            MLSConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", MLSConfig)
                                            (Description ""
                                             :> (Summary "Patch config for mls"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("mls"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              MLSConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 MLSConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", ExposeInvitationURLsToTeamAdminConfig)
                                       (Description ""
                                        :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("exposeInvitationURLsToTeamAdmin"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                ExposeInvitationURLsToTeamAdminConfig))))))))))
                                     :<|> (Named
                                             '("iput", ExposeInvitationURLsToTeamAdminConfig)
                                             (Description ""
                                              :> (Summary
                                                    "Put config for exposeInvitationURLsToTeamAdmin"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", ExposeInvitationURLsToTeamAdminConfig)
                                                  (Description ""
                                                   :> (Summary
                                                         "Patch config for exposeInvitationURLsToTeamAdmin"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("exposeInvitationURLsToTeamAdmin"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", OutlookCalIntegrationConfig)
                                             (Description ""
                                              :> (Summary "Get config for outlookCalIntegration"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("outlookCalIntegration"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      OutlookCalIntegrationConfig))))))))))
                                           :<|> (Named
                                                   '("iput", OutlookCalIntegrationConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Put config for outlookCalIntegration"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("outlookCalIntegration"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     OutlookCalIntegrationConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        OutlookCalIntegrationConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", OutlookCalIntegrationConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Patch config for outlookCalIntegration"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("outlookCalIntegration"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          OutlookCalIntegrationConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             OutlookCalIntegrationConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", MlsE2EIdConfig)
                                                   (Description ""
                                                    :> (Summary "Get config for mlsE2EId"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("mlsE2EId"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            MlsE2EIdConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", MlsE2EIdConfig)
                                                         (Description ""
                                                          :> (Summary "Put config for mlsE2EId"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mlsE2EId"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           MlsE2EIdConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              MlsE2EIdConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch", MlsE2EIdConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for mlsE2EId"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("mlsE2EId"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                MlsE2EIdConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   MlsE2EIdConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget", MlsMigrationConfig)
                                                         (Description ""
                                                          :> (Summary "Get config for mlsMigration"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("mlsMigration"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  MlsMigrationConfig))))))))))
                                                       :<|> (Named
                                                               '("iput", MlsMigrationConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for mlsMigration"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mlsMigration"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 MlsMigrationConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    MlsMigrationConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch", MlsMigrationConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for mlsMigration"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("mlsMigration"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      MlsMigrationConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         MlsMigrationConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget",
                                                                 EnforceFileDownloadLocationConfig)
                                                               (Description
                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                :> (Summary
                                                                      "Get config for enforceFileDownloadLocation"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        EnforceFileDownloadLocationConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput",
                                                                       EnforceFileDownloadLocationConfig)
                                                                     (Description
                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                      :> (Summary
                                                                            "Put config for enforceFileDownloadLocation"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          EnforceFileDownloadLocationConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            EnforceFileDownloadLocationConfig)
                                                                          (Description
                                                                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                           :> (Summary
                                                                                 "Patch config for enforceFileDownloadLocation"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("enforceFileDownloadLocation"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               EnforceFileDownloadLocationConfig)))))))))))))))
                                                            :<|> (Named
                                                                    '("iget",
                                                                      LimitedEventFanoutConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Get config for limitedEventFanout"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("limitedEventFanout"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             LimitedEventFanoutConfig))))))))))
                                                                  :<|> (Named
                                                                          '("iput",
                                                                            LimitedEventFanoutConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Put config for limitedEventFanout"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("limitedEventFanout"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (Feature
                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                       :> Put
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               LimitedEventFanoutConfig)))))))))))))
                                                                        :<|> Named
                                                                               '("ipatch",
                                                                                 LimitedEventFanoutConfig)
                                                                               (Description ""
                                                                                :> (Summary
                                                                                      "Patch config for limitedEventFanout"
                                                                                    :> (CanThrow
                                                                                          ('MissingPermission
                                                                                             'Nothing)
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> (CanThrow
                                                                                                      TeamFeatureError
                                                                                                    :> (CanThrowMany
                                                                                                          '[]
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("limitedEventFanout"
                                                                                                                        :> (ReqBody
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeaturePatch
                                                                                                                                 LimitedEventFanoutConfig)
                                                                                                                            :> Patch
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeature
                                                                                                                                    LimitedEventFanoutConfig)))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        '("iget", ClassifiedDomainsConfig)
        (Description ""
         :> (Summary "Get config for classifiedDomains"
             :> (CanThrow ('MissingPermission 'Nothing)
                 :> (CanThrow 'NotATeamMember
                     :> (CanThrow 'TeamNotFound
                         :> ("teams"
                             :> (Capture "tid" TeamId
                                 :> ("features"
                                     :> ("classifiedDomains"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature ClassifiedDomainsConfig))))))))))
      :<|> ((Named
               '("iget", ConferenceCallingConfig)
               (Description ""
                :> (Summary "Get config for conferenceCalling"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("conferenceCalling"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        ConferenceCallingConfig))))))))))
             :<|> (Named
                     '("iput", ConferenceCallingConfig)
                     (Description ""
                      :> (Summary "Put config for conferenceCalling"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("conferenceCalling"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       ConferenceCallingConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          ConferenceCallingConfig)))))))))))))
                   :<|> Named
                          '("ipatch", ConferenceCallingConfig)
                          (Description ""
                           :> (Summary "Patch config for conferenceCalling"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("conferenceCalling"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            ConferenceCallingConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               ConferenceCallingConfig)))))))))))))))
            :<|> ((Named
                     '("iget", SelfDeletingMessagesConfig)
                     (Description ""
                      :> (Summary "Get config for selfDeletingMessages"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("selfDeletingMessages"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              SelfDeletingMessagesConfig))))))))))
                   :<|> (Named
                           '("iput", SelfDeletingMessagesConfig)
                           (Description ""
                            :> (Summary "Put config for selfDeletingMessages"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("selfDeletingMessages"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             SelfDeletingMessagesConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                SelfDeletingMessagesConfig)))))))))))))
                         :<|> Named
                                '("ipatch", SelfDeletingMessagesConfig)
                                (Description ""
                                 :> (Summary "Patch config for selfDeletingMessages"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("selfDeletingMessages"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  SelfDeletingMessagesConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     SelfDeletingMessagesConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", GuestLinksConfig)
                           (Description ""
                            :> (Summary "Get config for conversationGuestLinks"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("conversationGuestLinks"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    GuestLinksConfig))))))))))
                         :<|> (Named
                                 '("iput", GuestLinksConfig)
                                 (Description ""
                                  :> (Summary "Put config for conversationGuestLinks"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("conversationGuestLinks"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   GuestLinksConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      GuestLinksConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", GuestLinksConfig)
                                      (Description ""
                                       :> (Summary "Patch config for conversationGuestLinks"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("conversationGuestLinks"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        GuestLinksConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           GuestLinksConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", SndFactorPasswordChallengeConfig)
                                 (Description ""
                                  :> (Summary "Get config for sndFactorPasswordChallenge"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("sndFactorPasswordChallenge"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          SndFactorPasswordChallengeConfig))))))))))
                               :<|> (Named
                                       '("iput", SndFactorPasswordChallengeConfig)
                                       (Description ""
                                        :> (Summary "Put config for sndFactorPasswordChallenge"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("sndFactorPasswordChallenge"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         SndFactorPasswordChallengeConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            SndFactorPasswordChallengeConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", SndFactorPasswordChallengeConfig)
                                            (Description ""
                                             :> (Summary
                                                   "Patch config for sndFactorPasswordChallenge"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("sndFactorPasswordChallenge"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              SndFactorPasswordChallengeConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 SndFactorPasswordChallengeConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", MLSConfig)
                                       (Description ""
                                        :> (Summary "Get config for mls"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("mls"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                MLSConfig))))))))))
                                     :<|> (Named
                                             '("iput", MLSConfig)
                                             (Description ""
                                              :> (Summary "Put config for mls"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("mls"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               MLSConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  MLSConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", MLSConfig)
                                                  (Description ""
                                                   :> (Summary "Patch config for mls"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("mls"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    MLSConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       MLSConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", ExposeInvitationURLsToTeamAdminConfig)
                                             (Description ""
                                              :> (Summary
                                                    "Get config for exposeInvitationURLsToTeamAdmin"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      ExposeInvitationURLsToTeamAdminConfig))))))))))
                                           :<|> (Named
                                                   '("iput", ExposeInvitationURLsToTeamAdminConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Put config for exposeInvitationURLsToTeamAdmin"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     ExposeInvitationURLsToTeamAdminConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch",
                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Patch config for exposeInvitationURLsToTeamAdmin"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", OutlookCalIntegrationConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Get config for outlookCalIntegration"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("outlookCalIntegration"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            OutlookCalIntegrationConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", OutlookCalIntegrationConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Put config for outlookCalIntegration"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("outlookCalIntegration"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           OutlookCalIntegrationConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              OutlookCalIntegrationConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch",
                                                                OutlookCalIntegrationConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for outlookCalIntegration"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("outlookCalIntegration"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                OutlookCalIntegrationConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   OutlookCalIntegrationConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget", MlsE2EIdConfig)
                                                         (Description ""
                                                          :> (Summary "Get config for mlsE2EId"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("mlsE2EId"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  MlsE2EIdConfig))))))))))
                                                       :<|> (Named
                                                               '("iput", MlsE2EIdConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for mlsE2EId"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mlsE2EId"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 MlsE2EIdConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    MlsE2EIdConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch", MlsE2EIdConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for mlsE2EId"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("mlsE2EId"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      MlsE2EIdConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         MlsE2EIdConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget", MlsMigrationConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Get config for mlsMigration"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("mlsMigration"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        MlsMigrationConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput", MlsMigrationConfig)
                                                                     (Description ""
                                                                      :> (Summary
                                                                            "Put config for mlsMigration"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mlsMigration"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       MlsMigrationConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          MlsMigrationConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            MlsMigrationConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Patch config for mlsMigration"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("mlsMigration"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            MlsMigrationConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               MlsMigrationConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("iget",
                                                                       EnforceFileDownloadLocationConfig)
                                                                     (Description
                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                      :> (Summary
                                                                            "Get config for enforceFileDownloadLocation"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                      :> Get
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              EnforceFileDownloadLocationConfig))))))))))
                                                                   :<|> (Named
                                                                           '("iput",
                                                                             EnforceFileDownloadLocationConfig)
                                                                           (Description
                                                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                            :> (Summary
                                                                                  "Put config for enforceFileDownloadLocation"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (Feature
                                                                                                                             EnforceFileDownloadLocationConfig)
                                                                                                                        :> Put
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                EnforceFileDownloadLocationConfig)))))))))))))
                                                                         :<|> Named
                                                                                '("ipatch",
                                                                                  EnforceFileDownloadLocationConfig)
                                                                                (Description
                                                                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                 :> (Summary
                                                                                       "Patch config for enforceFileDownloadLocation"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("enforceFileDownloadLocation"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeaturePatch
                                                                                                                                  EnforceFileDownloadLocationConfig)
                                                                                                                             :> Patch
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     EnforceFileDownloadLocationConfig)))))))))))))))
                                                                  :<|> (Named
                                                                          '("iget",
                                                                            LimitedEventFanoutConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Get config for limitedEventFanout"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("limitedEventFanout"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   LimitedEventFanoutConfig))))))))))
                                                                        :<|> (Named
                                                                                '("iput",
                                                                                  LimitedEventFanoutConfig)
                                                                                (Description ""
                                                                                 :> (Summary
                                                                                       "Put config for limitedEventFanout"
                                                                                     :> (CanThrow
                                                                                           ('MissingPermission
                                                                                              'Nothing)
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       TeamFeatureError
                                                                                                     :> (CanThrowMany
                                                                                                           '[]
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("limitedEventFanout"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               (Feature
                                                                                                                                  LimitedEventFanoutConfig)
                                                                                                                             :> Put
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     LimitedEventFanoutConfig)))))))))))))
                                                                              :<|> Named
                                                                                     '("ipatch",
                                                                                       LimitedEventFanoutConfig)
                                                                                     (Description ""
                                                                                      :> (Summary
                                                                                            "Patch config for limitedEventFanout"
                                                                                          :> (CanThrow
                                                                                                ('MissingPermission
                                                                                                   'Nothing)
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> (CanThrow
                                                                                                            TeamFeatureError
                                                                                                          :> (CanThrowMany
                                                                                                                '[]
                                                                                                              :> ("teams"
                                                                                                                  :> (Capture
                                                                                                                        "tid"
                                                                                                                        TeamId
                                                                                                                      :> ("features"
                                                                                                                          :> ("limitedEventFanout"
                                                                                                                              :> (ReqBody
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeaturePatch
                                                                                                                                       LimitedEventFanoutConfig)
                                                                                                                                  :> Patch
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeature
                                                                                                                                          LimitedEventFanoutConfig))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", ConferenceCallingConfig)
     (Description ""
      :> (Summary "Get config for conferenceCalling"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("conferenceCalling"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature ConferenceCallingConfig))))))))))
   :<|> (Named
           '("iput", ConferenceCallingConfig)
           (Description ""
            :> (Summary "Put config for conferenceCalling"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("conferenceCalling"
                                                    :> (ReqBody
                                                          '[JSON] (Feature ConferenceCallingConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                ConferenceCallingConfig)))))))))))))
         :<|> Named
                '("ipatch", ConferenceCallingConfig)
                (Description ""
                 :> (Summary "Patch config for conferenceCalling"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("conferenceCalling"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  ConferenceCallingConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     ConferenceCallingConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", ConferenceCallingConfig)
     (Description (FeatureAPIDesc ConferenceCallingConfig)
      :> (Summary
            (AppendSymbol
               "Get config for " (FeatureSymbol ConferenceCallingConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol ConferenceCallingConfig
                                      :> Get
                                           '[JSON]
                                           (LockableFeature ConferenceCallingConfig))))))))))
   :<|> (Named
           '("iput", ConferenceCallingConfig)
           (Description (FeatureAPIDesc ConferenceCallingConfig)
            :> (Summary
                  (AppendSymbol
                     "Put config for " (FeatureSymbol ConferenceCallingConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors ConferenceCallingConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol ConferenceCallingConfig
                                                    :> (ReqBody
                                                          '[JSON] (Feature ConferenceCallingConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                ConferenceCallingConfig)))))))))))))
         :<|> Named
                '("ipatch", ConferenceCallingConfig)
                (Description (FeatureAPIDesc ConferenceCallingConfig)
                 :> (Summary
                       (AppendSymbol
                          "Patch config for " (FeatureSymbol ConferenceCallingConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany (FeatureErrors ConferenceCallingConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol ConferenceCallingConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  ConferenceCallingConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     ConferenceCallingConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", ConferenceCallingConfig)
     (Description ""
      :> (Summary "Get config for conferenceCalling"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("conferenceCalling"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature ConferenceCallingConfig))))))))))
   :<|> (Named
           '("iput", ConferenceCallingConfig)
           (Description ""
            :> (Summary "Put config for conferenceCalling"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("conferenceCalling"
                                                    :> (ReqBody
                                                          '[JSON] (Feature ConferenceCallingConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                ConferenceCallingConfig)))))))))))))
         :<|> Named
                '("ipatch", ConferenceCallingConfig)
                (Description ""
                 :> (Summary "Patch config for conferenceCalling"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("conferenceCalling"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  ConferenceCallingConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     ConferenceCallingConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", SelfDeletingMessagesConfig)
         (Description ""
          :> (Summary "Get config for selfDeletingMessages"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("selfDeletingMessages"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature SelfDeletingMessagesConfig))))))))))
       :<|> (Named
               '("iput", SelfDeletingMessagesConfig)
               (Description ""
                :> (Summary "Put config for selfDeletingMessages"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("selfDeletingMessages"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature SelfDeletingMessagesConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SelfDeletingMessagesConfig)))))))))))))
             :<|> Named
                    '("ipatch", SelfDeletingMessagesConfig)
                    (Description ""
                     :> (Summary "Patch config for selfDeletingMessages"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("selfDeletingMessages"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      SelfDeletingMessagesConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SelfDeletingMessagesConfig)))))))))))))))
      :<|> ((Named
               '("iget", GuestLinksConfig)
               (Description ""
                :> (Summary "Get config for conversationGuestLinks"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("conversationGuestLinks"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature GuestLinksConfig))))))))))
             :<|> (Named
                     '("iput", GuestLinksConfig)
                     (Description ""
                      :> (Summary "Put config for conversationGuestLinks"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("conversationGuestLinks"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature GuestLinksConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          GuestLinksConfig)))))))))))))
                   :<|> Named
                          '("ipatch", GuestLinksConfig)
                          (Description ""
                           :> (Summary "Patch config for conversationGuestLinks"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("conversationGuestLinks"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            GuestLinksConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               GuestLinksConfig)))))))))))))))
            :<|> ((Named
                     '("iget", SndFactorPasswordChallengeConfig)
                     (Description ""
                      :> (Summary "Get config for sndFactorPasswordChallenge"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("sndFactorPasswordChallenge"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              SndFactorPasswordChallengeConfig))))))))))
                   :<|> (Named
                           '("iput", SndFactorPasswordChallengeConfig)
                           (Description ""
                            :> (Summary "Put config for sndFactorPasswordChallenge"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("sndFactorPasswordChallenge"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             SndFactorPasswordChallengeConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                SndFactorPasswordChallengeConfig)))))))))))))
                         :<|> Named
                                '("ipatch", SndFactorPasswordChallengeConfig)
                                (Description ""
                                 :> (Summary "Patch config for sndFactorPasswordChallenge"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("sndFactorPasswordChallenge"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  SndFactorPasswordChallengeConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     SndFactorPasswordChallengeConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", MLSConfig)
                           (Description ""
                            :> (Summary "Get config for mls"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("mls"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    MLSConfig))))))))))
                         :<|> (Named
                                 '("iput", MLSConfig)
                                 (Description ""
                                  :> (Summary "Put config for mls"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("mls"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature MLSConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      MLSConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", MLSConfig)
                                      (Description ""
                                       :> (Summary "Patch config for mls"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("mls"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        MLSConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           MLSConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", ExposeInvitationURLsToTeamAdminConfig)
                                 (Description ""
                                  :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("exposeInvitationURLsToTeamAdmin"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          ExposeInvitationURLsToTeamAdminConfig))))))))))
                               :<|> (Named
                                       '("iput", ExposeInvitationURLsToTeamAdminConfig)
                                       (Description ""
                                        :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", ExposeInvitationURLsToTeamAdminConfig)
                                            (Description ""
                                             :> (Summary
                                                   "Patch config for exposeInvitationURLsToTeamAdmin"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("exposeInvitationURLsToTeamAdmin"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", OutlookCalIntegrationConfig)
                                       (Description ""
                                        :> (Summary "Get config for outlookCalIntegration"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("outlookCalIntegration"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                OutlookCalIntegrationConfig))))))))))
                                     :<|> (Named
                                             '("iput", OutlookCalIntegrationConfig)
                                             (Description ""
                                              :> (Summary "Put config for outlookCalIntegration"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("outlookCalIntegration"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               OutlookCalIntegrationConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  OutlookCalIntegrationConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", OutlookCalIntegrationConfig)
                                                  (Description ""
                                                   :> (Summary
                                                         "Patch config for outlookCalIntegration"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("outlookCalIntegration"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    OutlookCalIntegrationConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       OutlookCalIntegrationConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", MlsE2EIdConfig)
                                             (Description ""
                                              :> (Summary "Get config for mlsE2EId"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("mlsE2EId"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      MlsE2EIdConfig))))))))))
                                           :<|> (Named
                                                   '("iput", MlsE2EIdConfig)
                                                   (Description ""
                                                    :> (Summary "Put config for mlsE2EId"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mlsE2EId"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     MlsE2EIdConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        MlsE2EIdConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", MlsE2EIdConfig)
                                                        (Description ""
                                                         :> (Summary "Patch config for mlsE2EId"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("mlsE2EId"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          MlsE2EIdConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             MlsE2EIdConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", MlsMigrationConfig)
                                                   (Description ""
                                                    :> (Summary "Get config for mlsMigration"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("mlsMigration"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            MlsMigrationConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", MlsMigrationConfig)
                                                         (Description ""
                                                          :> (Summary "Put config for mlsMigration"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mlsMigration"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           MlsMigrationConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              MlsMigrationConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch", MlsMigrationConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for mlsMigration"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("mlsMigration"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                MlsMigrationConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   MlsMigrationConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget",
                                                           EnforceFileDownloadLocationConfig)
                                                         (Description
                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                          :> (Summary
                                                                "Get config for enforceFileDownloadLocation"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("enforceFileDownloadLocation"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  EnforceFileDownloadLocationConfig))))))))))
                                                       :<|> (Named
                                                               '("iput",
                                                                 EnforceFileDownloadLocationConfig)
                                                               (Description
                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                :> (Summary
                                                                      "Put config for enforceFileDownloadLocation"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    EnforceFileDownloadLocationConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch",
                                                                      EnforceFileDownloadLocationConfig)
                                                                    (Description
                                                                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                     :> (Summary
                                                                           "Patch config for enforceFileDownloadLocation"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("enforceFileDownloadLocation"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         EnforceFileDownloadLocationConfig)))))))))))))))
                                                      :<|> (Named
                                                              '("iget", LimitedEventFanoutConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Get config for limitedEventFanout"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("limitedEventFanout"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       LimitedEventFanoutConfig))))))))))
                                                            :<|> (Named
                                                                    '("iput",
                                                                      LimitedEventFanoutConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Put config for limitedEventFanout"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("limitedEventFanout"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (Feature
                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                 :> Put
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         LimitedEventFanoutConfig)))))))))))))
                                                                  :<|> Named
                                                                         '("ipatch",
                                                                           LimitedEventFanoutConfig)
                                                                         (Description ""
                                                                          :> (Summary
                                                                                "Patch config for limitedEventFanout"
                                                                              :> (CanThrow
                                                                                    ('MissingPermission
                                                                                       'Nothing)
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> (CanThrow
                                                                                                TeamFeatureError
                                                                                              :> (CanThrowMany
                                                                                                    '[]
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("limitedEventFanout"
                                                                                                                  :> (ReqBody
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeaturePatch
                                                                                                                           LimitedEventFanoutConfig)
                                                                                                                      :> Patch
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              LimitedEventFanoutConfig))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", ConferenceCallingConfig)
         (Description ""
          :> (Summary "Get config for conferenceCalling"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("conferenceCalling"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature ConferenceCallingConfig))))))))))
       :<|> (Named
               '("iput", ConferenceCallingConfig)
               (Description ""
                :> (Summary "Put config for conferenceCalling"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("conferenceCalling"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature ConferenceCallingConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    ConferenceCallingConfig)))))))))))))
             :<|> Named
                    '("ipatch", ConferenceCallingConfig)
                    (Description ""
                     :> (Summary "Patch config for conferenceCalling"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("conferenceCalling"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      ConferenceCallingConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         ConferenceCallingConfig)))))))))))))))
      :<|> ((Named
               '("iget", SelfDeletingMessagesConfig)
               (Description ""
                :> (Summary "Get config for selfDeletingMessages"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("selfDeletingMessages"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        SelfDeletingMessagesConfig))))))))))
             :<|> (Named
                     '("iput", SelfDeletingMessagesConfig)
                     (Description ""
                      :> (Summary "Put config for selfDeletingMessages"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("selfDeletingMessages"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       SelfDeletingMessagesConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          SelfDeletingMessagesConfig)))))))))))))
                   :<|> Named
                          '("ipatch", SelfDeletingMessagesConfig)
                          (Description ""
                           :> (Summary "Patch config for selfDeletingMessages"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("selfDeletingMessages"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            SelfDeletingMessagesConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SelfDeletingMessagesConfig)))))))))))))))
            :<|> ((Named
                     '("iget", GuestLinksConfig)
                     (Description ""
                      :> (Summary "Get config for conversationGuestLinks"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("conversationGuestLinks"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              GuestLinksConfig))))))))))
                   :<|> (Named
                           '("iput", GuestLinksConfig)
                           (Description ""
                            :> (Summary "Put config for conversationGuestLinks"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("conversationGuestLinks"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature GuestLinksConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                GuestLinksConfig)))))))))))))
                         :<|> Named
                                '("ipatch", GuestLinksConfig)
                                (Description ""
                                 :> (Summary "Patch config for conversationGuestLinks"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("conversationGuestLinks"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  GuestLinksConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     GuestLinksConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", SndFactorPasswordChallengeConfig)
                           (Description ""
                            :> (Summary "Get config for sndFactorPasswordChallenge"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("sndFactorPasswordChallenge"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SndFactorPasswordChallengeConfig))))))))))
                         :<|> (Named
                                 '("iput", SndFactorPasswordChallengeConfig)
                                 (Description ""
                                  :> (Summary "Put config for sndFactorPasswordChallenge"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("sndFactorPasswordChallenge"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   SndFactorPasswordChallengeConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      SndFactorPasswordChallengeConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", SndFactorPasswordChallengeConfig)
                                      (Description ""
                                       :> (Summary "Patch config for sndFactorPasswordChallenge"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("sndFactorPasswordChallenge"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        SndFactorPasswordChallengeConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           SndFactorPasswordChallengeConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", MLSConfig)
                                 (Description ""
                                  :> (Summary "Get config for mls"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("mls"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          MLSConfig))))))))))
                               :<|> (Named
                                       '("iput", MLSConfig)
                                       (Description ""
                                        :> (Summary "Put config for mls"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("mls"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         MLSConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            MLSConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", MLSConfig)
                                            (Description ""
                                             :> (Summary "Patch config for mls"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("mls"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              MLSConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 MLSConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", ExposeInvitationURLsToTeamAdminConfig)
                                       (Description ""
                                        :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("exposeInvitationURLsToTeamAdmin"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                ExposeInvitationURLsToTeamAdminConfig))))))))))
                                     :<|> (Named
                                             '("iput", ExposeInvitationURLsToTeamAdminConfig)
                                             (Description ""
                                              :> (Summary
                                                    "Put config for exposeInvitationURLsToTeamAdmin"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", ExposeInvitationURLsToTeamAdminConfig)
                                                  (Description ""
                                                   :> (Summary
                                                         "Patch config for exposeInvitationURLsToTeamAdmin"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("exposeInvitationURLsToTeamAdmin"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", OutlookCalIntegrationConfig)
                                             (Description ""
                                              :> (Summary "Get config for outlookCalIntegration"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("outlookCalIntegration"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      OutlookCalIntegrationConfig))))))))))
                                           :<|> (Named
                                                   '("iput", OutlookCalIntegrationConfig)
                                                   (Description ""
                                                    :> (Summary
                                                          "Put config for outlookCalIntegration"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("outlookCalIntegration"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     OutlookCalIntegrationConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        OutlookCalIntegrationConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", OutlookCalIntegrationConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Patch config for outlookCalIntegration"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("outlookCalIntegration"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          OutlookCalIntegrationConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             OutlookCalIntegrationConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", MlsE2EIdConfig)
                                                   (Description ""
                                                    :> (Summary "Get config for mlsE2EId"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("mlsE2EId"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            MlsE2EIdConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", MlsE2EIdConfig)
                                                         (Description ""
                                                          :> (Summary "Put config for mlsE2EId"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mlsE2EId"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           MlsE2EIdConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              MlsE2EIdConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch", MlsE2EIdConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for mlsE2EId"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("mlsE2EId"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                MlsE2EIdConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   MlsE2EIdConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget", MlsMigrationConfig)
                                                         (Description ""
                                                          :> (Summary "Get config for mlsMigration"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("mlsMigration"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  MlsMigrationConfig))))))))))
                                                       :<|> (Named
                                                               '("iput", MlsMigrationConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Put config for mlsMigration"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mlsMigration"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 MlsMigrationConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    MlsMigrationConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch", MlsMigrationConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Patch config for mlsMigration"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("mlsMigration"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      MlsMigrationConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         MlsMigrationConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("iget",
                                                                 EnforceFileDownloadLocationConfig)
                                                               (Description
                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                :> (Summary
                                                                      "Get config for enforceFileDownloadLocation"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        EnforceFileDownloadLocationConfig))))))))))
                                                             :<|> (Named
                                                                     '("iput",
                                                                       EnforceFileDownloadLocationConfig)
                                                                     (Description
                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                      :> (Summary
                                                                            "Put config for enforceFileDownloadLocation"
                                                                          :> (CanThrow
                                                                                ('MissingPermission
                                                                                   'Nothing)
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> (CanThrow
                                                                                            TeamFeatureError
                                                                                          :> (CanThrowMany
                                                                                                '[]
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    (Feature
                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                  :> Put
                                                                                                                       '[JSON]
                                                                                                                       (LockableFeature
                                                                                                                          EnforceFileDownloadLocationConfig)))))))))))))
                                                                   :<|> Named
                                                                          '("ipatch",
                                                                            EnforceFileDownloadLocationConfig)
                                                                          (Description
                                                                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                           :> (Summary
                                                                                 "Patch config for enforceFileDownloadLocation"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("enforceFileDownloadLocation"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeaturePatch
                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                       :> Patch
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               EnforceFileDownloadLocationConfig)))))))))))))))
                                                            :<|> (Named
                                                                    '("iget",
                                                                      LimitedEventFanoutConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Get config for limitedEventFanout"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("limitedEventFanout"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             LimitedEventFanoutConfig))))))))))
                                                                  :<|> (Named
                                                                          '("iput",
                                                                            LimitedEventFanoutConfig)
                                                                          (Description ""
                                                                           :> (Summary
                                                                                 "Put config for limitedEventFanout"
                                                                               :> (CanThrow
                                                                                     ('MissingPermission
                                                                                        'Nothing)
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 TeamFeatureError
                                                                                               :> (CanThrowMany
                                                                                                     '[]
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("limitedEventFanout"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         (Feature
                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                       :> Put
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               LimitedEventFanoutConfig)))))))))))))
                                                                        :<|> Named
                                                                               '("ipatch",
                                                                                 LimitedEventFanoutConfig)
                                                                               (Description ""
                                                                                :> (Summary
                                                                                      "Patch config for limitedEventFanout"
                                                                                    :> (CanThrow
                                                                                          ('MissingPermission
                                                                                             'Nothing)
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> (CanThrow
                                                                                                      TeamFeatureError
                                                                                                    :> (CanThrowMany
                                                                                                          '[]
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("limitedEventFanout"
                                                                                                                        :> (ReqBody
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeaturePatch
                                                                                                                                 LimitedEventFanoutConfig)
                                                                                                                            :> Patch
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeature
                                                                                                                                    LimitedEventFanoutConfig)))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", SelfDeletingMessagesConfig)
     (Description ""
      :> (Summary "Get config for selfDeletingMessages"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("selfDeletingMessages"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature SelfDeletingMessagesConfig))))))))))
   :<|> (Named
           '("iput", SelfDeletingMessagesConfig)
           (Description ""
            :> (Summary "Put config for selfDeletingMessages"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("selfDeletingMessages"
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature SelfDeletingMessagesConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                SelfDeletingMessagesConfig)))))))))))))
         :<|> Named
                '("ipatch", SelfDeletingMessagesConfig)
                (Description ""
                 :> (Summary "Patch config for selfDeletingMessages"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("selfDeletingMessages"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  SelfDeletingMessagesConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SelfDeletingMessagesConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", SelfDeletingMessagesConfig)
     (Description (FeatureAPIDesc SelfDeletingMessagesConfig)
      :> (Summary
            (AppendSymbol
               "Get config for " (FeatureSymbol SelfDeletingMessagesConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol SelfDeletingMessagesConfig
                                      :> Get
                                           '[JSON]
                                           (LockableFeature SelfDeletingMessagesConfig))))))))))
   :<|> (Named
           '("iput", SelfDeletingMessagesConfig)
           (Description (FeatureAPIDesc SelfDeletingMessagesConfig)
            :> (Summary
                  (AppendSymbol
                     "Put config for " (FeatureSymbol SelfDeletingMessagesConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors SelfDeletingMessagesConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol SelfDeletingMessagesConfig
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature SelfDeletingMessagesConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                SelfDeletingMessagesConfig)))))))))))))
         :<|> Named
                '("ipatch", SelfDeletingMessagesConfig)
                (Description (FeatureAPIDesc SelfDeletingMessagesConfig)
                 :> (Summary
                       (AppendSymbol
                          "Patch config for " (FeatureSymbol SelfDeletingMessagesConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany (FeatureErrors SelfDeletingMessagesConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol SelfDeletingMessagesConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  SelfDeletingMessagesConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SelfDeletingMessagesConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", SelfDeletingMessagesConfig)
     (Description ""
      :> (Summary "Get config for selfDeletingMessages"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("selfDeletingMessages"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature SelfDeletingMessagesConfig))))))))))
   :<|> (Named
           '("iput", SelfDeletingMessagesConfig)
           (Description ""
            :> (Summary "Put config for selfDeletingMessages"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("selfDeletingMessages"
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature SelfDeletingMessagesConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                SelfDeletingMessagesConfig)))))))))))))
         :<|> Named
                '("ipatch", SelfDeletingMessagesConfig)
                (Description ""
                 :> (Summary "Patch config for selfDeletingMessages"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("selfDeletingMessages"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  SelfDeletingMessagesConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SelfDeletingMessagesConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", GuestLinksConfig)
         (Description ""
          :> (Summary "Get config for conversationGuestLinks"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("conversationGuestLinks"
                                          :> Get '[JSON] (LockableFeature GuestLinksConfig))))))))))
       :<|> (Named
               '("iput", GuestLinksConfig)
               (Description ""
                :> (Summary "Put config for conversationGuestLinks"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("conversationGuestLinks"
                                                        :> (ReqBody
                                                              '[JSON] (Feature GuestLinksConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    GuestLinksConfig)))))))))))))
             :<|> Named
                    '("ipatch", GuestLinksConfig)
                    (Description ""
                     :> (Summary "Patch config for conversationGuestLinks"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("conversationGuestLinks"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      GuestLinksConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         GuestLinksConfig)))))))))))))))
      :<|> ((Named
               '("iget", SndFactorPasswordChallengeConfig)
               (Description ""
                :> (Summary "Get config for sndFactorPasswordChallenge"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("sndFactorPasswordChallenge"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        SndFactorPasswordChallengeConfig))))))))))
             :<|> (Named
                     '("iput", SndFactorPasswordChallengeConfig)
                     (Description ""
                      :> (Summary "Put config for sndFactorPasswordChallenge"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("sndFactorPasswordChallenge"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       SndFactorPasswordChallengeConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          SndFactorPasswordChallengeConfig)))))))))))))
                   :<|> Named
                          '("ipatch", SndFactorPasswordChallengeConfig)
                          (Description ""
                           :> (Summary "Patch config for sndFactorPasswordChallenge"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("sndFactorPasswordChallenge"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            SndFactorPasswordChallengeConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SndFactorPasswordChallengeConfig)))))))))))))))
            :<|> ((Named
                     '("iget", MLSConfig)
                     (Description ""
                      :> (Summary "Get config for mls"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("mls"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature MLSConfig))))))))))
                   :<|> (Named
                           '("iput", MLSConfig)
                           (Description ""
                            :> (Summary "Put config for mls"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("mls"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature MLSConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                MLSConfig)))))))))))))
                         :<|> Named
                                '("ipatch", MLSConfig)
                                (Description ""
                                 :> (Summary "Patch config for mls"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("mls"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  MLSConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     MLSConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", ExposeInvitationURLsToTeamAdminConfig)
                           (Description ""
                            :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    ExposeInvitationURLsToTeamAdminConfig))))))))))
                         :<|> (Named
                                 '("iput", ExposeInvitationURLsToTeamAdminConfig)
                                 (Description ""
                                  :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", ExposeInvitationURLsToTeamAdminConfig)
                                      (Description ""
                                       :> (Summary
                                             "Patch config for exposeInvitationURLsToTeamAdmin"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("exposeInvitationURLsToTeamAdmin"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", OutlookCalIntegrationConfig)
                                 (Description ""
                                  :> (Summary "Get config for outlookCalIntegration"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("outlookCalIntegration"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          OutlookCalIntegrationConfig))))))))))
                               :<|> (Named
                                       '("iput", OutlookCalIntegrationConfig)
                                       (Description ""
                                        :> (Summary "Put config for outlookCalIntegration"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("outlookCalIntegration"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         OutlookCalIntegrationConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            OutlookCalIntegrationConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", OutlookCalIntegrationConfig)
                                            (Description ""
                                             :> (Summary "Patch config for outlookCalIntegration"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("outlookCalIntegration"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              OutlookCalIntegrationConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 OutlookCalIntegrationConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", MlsE2EIdConfig)
                                       (Description ""
                                        :> (Summary "Get config for mlsE2EId"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("mlsE2EId"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                MlsE2EIdConfig))))))))))
                                     :<|> (Named
                                             '("iput", MlsE2EIdConfig)
                                             (Description ""
                                              :> (Summary "Put config for mlsE2EId"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("mlsE2EId"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               MlsE2EIdConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  MlsE2EIdConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", MlsE2EIdConfig)
                                                  (Description ""
                                                   :> (Summary "Patch config for mlsE2EId"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("mlsE2EId"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    MlsE2EIdConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       MlsE2EIdConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", MlsMigrationConfig)
                                             (Description ""
                                              :> (Summary "Get config for mlsMigration"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("mlsMigration"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      MlsMigrationConfig))))))))))
                                           :<|> (Named
                                                   '("iput", MlsMigrationConfig)
                                                   (Description ""
                                                    :> (Summary "Put config for mlsMigration"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mlsMigration"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     MlsMigrationConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        MlsMigrationConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", MlsMigrationConfig)
                                                        (Description ""
                                                         :> (Summary "Patch config for mlsMigration"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("mlsMigration"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          MlsMigrationConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             MlsMigrationConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", EnforceFileDownloadLocationConfig)
                                                   (Description
                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                    :> (Summary
                                                          "Get config for enforceFileDownloadLocation"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("enforceFileDownloadLocation"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            EnforceFileDownloadLocationConfig))))))))))
                                                 :<|> (Named
                                                         '("iput",
                                                           EnforceFileDownloadLocationConfig)
                                                         (Description
                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                          :> (Summary
                                                                "Put config for enforceFileDownloadLocation"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              EnforceFileDownloadLocationConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch",
                                                                EnforceFileDownloadLocationConfig)
                                                              (Description
                                                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                               :> (Summary
                                                                     "Patch config for enforceFileDownloadLocation"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("enforceFileDownloadLocation"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   EnforceFileDownloadLocationConfig)))))))))))))))
                                                :<|> (Named
                                                        '("iget", LimitedEventFanoutConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Get config for limitedEventFanout"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("limitedEventFanout"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 LimitedEventFanoutConfig))))))))))
                                                      :<|> (Named
                                                              '("iput", LimitedEventFanoutConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Put config for limitedEventFanout"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("limitedEventFanout"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (Feature
                                                                                                                LimitedEventFanoutConfig)
                                                                                                           :> Put
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   LimitedEventFanoutConfig)))))))))))))
                                                            :<|> Named
                                                                   '("ipatch",
                                                                     LimitedEventFanoutConfig)
                                                                   (Description ""
                                                                    :> (Summary
                                                                          "Patch config for limitedEventFanout"
                                                                        :> (CanThrow
                                                                              ('MissingPermission
                                                                                 'Nothing)
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> (CanThrow
                                                                                          TeamFeatureError
                                                                                        :> (CanThrowMany
                                                                                              '[]
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("limitedEventFanout"
                                                                                                            :> (ReqBody
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeaturePatch
                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                :> Patch
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        LimitedEventFanoutConfig)))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", SelfDeletingMessagesConfig)
         (Description ""
          :> (Summary "Get config for selfDeletingMessages"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("selfDeletingMessages"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature SelfDeletingMessagesConfig))))))))))
       :<|> (Named
               '("iput", SelfDeletingMessagesConfig)
               (Description ""
                :> (Summary "Put config for selfDeletingMessages"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("selfDeletingMessages"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature SelfDeletingMessagesConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SelfDeletingMessagesConfig)))))))))))))
             :<|> Named
                    '("ipatch", SelfDeletingMessagesConfig)
                    (Description ""
                     :> (Summary "Patch config for selfDeletingMessages"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("selfDeletingMessages"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      SelfDeletingMessagesConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SelfDeletingMessagesConfig)))))))))))))))
      :<|> ((Named
               '("iget", GuestLinksConfig)
               (Description ""
                :> (Summary "Get config for conversationGuestLinks"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("conversationGuestLinks"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature GuestLinksConfig))))))))))
             :<|> (Named
                     '("iput", GuestLinksConfig)
                     (Description ""
                      :> (Summary "Put config for conversationGuestLinks"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("conversationGuestLinks"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature GuestLinksConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          GuestLinksConfig)))))))))))))
                   :<|> Named
                          '("ipatch", GuestLinksConfig)
                          (Description ""
                           :> (Summary "Patch config for conversationGuestLinks"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("conversationGuestLinks"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            GuestLinksConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               GuestLinksConfig)))))))))))))))
            :<|> ((Named
                     '("iget", SndFactorPasswordChallengeConfig)
                     (Description ""
                      :> (Summary "Get config for sndFactorPasswordChallenge"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("sndFactorPasswordChallenge"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              SndFactorPasswordChallengeConfig))))))))))
                   :<|> (Named
                           '("iput", SndFactorPasswordChallengeConfig)
                           (Description ""
                            :> (Summary "Put config for sndFactorPasswordChallenge"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("sndFactorPasswordChallenge"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             SndFactorPasswordChallengeConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                SndFactorPasswordChallengeConfig)))))))))))))
                         :<|> Named
                                '("ipatch", SndFactorPasswordChallengeConfig)
                                (Description ""
                                 :> (Summary "Patch config for sndFactorPasswordChallenge"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("sndFactorPasswordChallenge"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  SndFactorPasswordChallengeConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     SndFactorPasswordChallengeConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", MLSConfig)
                           (Description ""
                            :> (Summary "Get config for mls"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("mls"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    MLSConfig))))))))))
                         :<|> (Named
                                 '("iput", MLSConfig)
                                 (Description ""
                                  :> (Summary "Put config for mls"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("mls"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature MLSConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      MLSConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", MLSConfig)
                                      (Description ""
                                       :> (Summary "Patch config for mls"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("mls"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        MLSConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           MLSConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", ExposeInvitationURLsToTeamAdminConfig)
                                 (Description ""
                                  :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("exposeInvitationURLsToTeamAdmin"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          ExposeInvitationURLsToTeamAdminConfig))))))))))
                               :<|> (Named
                                       '("iput", ExposeInvitationURLsToTeamAdminConfig)
                                       (Description ""
                                        :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", ExposeInvitationURLsToTeamAdminConfig)
                                            (Description ""
                                             :> (Summary
                                                   "Patch config for exposeInvitationURLsToTeamAdmin"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("exposeInvitationURLsToTeamAdmin"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", OutlookCalIntegrationConfig)
                                       (Description ""
                                        :> (Summary "Get config for outlookCalIntegration"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("outlookCalIntegration"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                OutlookCalIntegrationConfig))))))))))
                                     :<|> (Named
                                             '("iput", OutlookCalIntegrationConfig)
                                             (Description ""
                                              :> (Summary "Put config for outlookCalIntegration"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("outlookCalIntegration"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               OutlookCalIntegrationConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  OutlookCalIntegrationConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", OutlookCalIntegrationConfig)
                                                  (Description ""
                                                   :> (Summary
                                                         "Patch config for outlookCalIntegration"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("outlookCalIntegration"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    OutlookCalIntegrationConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       OutlookCalIntegrationConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", MlsE2EIdConfig)
                                             (Description ""
                                              :> (Summary "Get config for mlsE2EId"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("mlsE2EId"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      MlsE2EIdConfig))))))))))
                                           :<|> (Named
                                                   '("iput", MlsE2EIdConfig)
                                                   (Description ""
                                                    :> (Summary "Put config for mlsE2EId"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mlsE2EId"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     MlsE2EIdConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        MlsE2EIdConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", MlsE2EIdConfig)
                                                        (Description ""
                                                         :> (Summary "Patch config for mlsE2EId"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("mlsE2EId"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          MlsE2EIdConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             MlsE2EIdConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", MlsMigrationConfig)
                                                   (Description ""
                                                    :> (Summary "Get config for mlsMigration"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("mlsMigration"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            MlsMigrationConfig))))))))))
                                                 :<|> (Named
                                                         '("iput", MlsMigrationConfig)
                                                         (Description ""
                                                          :> (Summary "Put config for mlsMigration"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mlsMigration"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           MlsMigrationConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              MlsMigrationConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch", MlsMigrationConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Patch config for mlsMigration"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("mlsMigration"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                MlsMigrationConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   MlsMigrationConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("iget",
                                                           EnforceFileDownloadLocationConfig)
                                                         (Description
                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                          :> (Summary
                                                                "Get config for enforceFileDownloadLocation"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("enforceFileDownloadLocation"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  EnforceFileDownloadLocationConfig))))))))))
                                                       :<|> (Named
                                                               '("iput",
                                                                 EnforceFileDownloadLocationConfig)
                                                               (Description
                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                :> (Summary
                                                                      "Put config for enforceFileDownloadLocation"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (Feature
                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                            :> Put
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    EnforceFileDownloadLocationConfig)))))))))))))
                                                             :<|> Named
                                                                    '("ipatch",
                                                                      EnforceFileDownloadLocationConfig)
                                                                    (Description
                                                                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                     :> (Summary
                                                                           "Patch config for enforceFileDownloadLocation"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("enforceFileDownloadLocation"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeaturePatch
                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                 :> Patch
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         EnforceFileDownloadLocationConfig)))))))))))))))
                                                      :<|> (Named
                                                              '("iget", LimitedEventFanoutConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Get config for limitedEventFanout"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("limitedEventFanout"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       LimitedEventFanoutConfig))))))))))
                                                            :<|> (Named
                                                                    '("iput",
                                                                      LimitedEventFanoutConfig)
                                                                    (Description ""
                                                                     :> (Summary
                                                                           "Put config for limitedEventFanout"
                                                                         :> (CanThrow
                                                                               ('MissingPermission
                                                                                  'Nothing)
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           TeamFeatureError
                                                                                         :> (CanThrowMany
                                                                                               '[]
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("limitedEventFanout"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   (Feature
                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                 :> Put
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         LimitedEventFanoutConfig)))))))))))))
                                                                  :<|> Named
                                                                         '("ipatch",
                                                                           LimitedEventFanoutConfig)
                                                                         (Description ""
                                                                          :> (Summary
                                                                                "Patch config for limitedEventFanout"
                                                                              :> (CanThrow
                                                                                    ('MissingPermission
                                                                                       'Nothing)
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> (CanThrow
                                                                                                TeamFeatureError
                                                                                              :> (CanThrowMany
                                                                                                    '[]
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("limitedEventFanout"
                                                                                                                  :> (ReqBody
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeaturePatch
                                                                                                                           LimitedEventFanoutConfig)
                                                                                                                      :> Patch
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              LimitedEventFanoutConfig))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", GuestLinksConfig)
     (Description ""
      :> (Summary "Get config for conversationGuestLinks"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("conversationGuestLinks"
                                      :> Get '[JSON] (LockableFeature GuestLinksConfig))))))))))
   :<|> (Named
           '("iput", GuestLinksConfig)
           (Description ""
            :> (Summary "Put config for conversationGuestLinks"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("conversationGuestLinks"
                                                    :> (ReqBody '[JSON] (Feature GuestLinksConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                GuestLinksConfig)))))))))))))
         :<|> Named
                '("ipatch", GuestLinksConfig)
                (Description ""
                 :> (Summary "Patch config for conversationGuestLinks"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("conversationGuestLinks"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  GuestLinksConfig)
                                                             :> Patch
                                                                  '[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
     '("iget", GuestLinksConfig)
     (Description (FeatureAPIDesc GuestLinksConfig)
      :> (Summary
            (AppendSymbol "Get config for " (FeatureSymbol GuestLinksConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol GuestLinksConfig
                                      :> Get '[JSON] (LockableFeature GuestLinksConfig))))))))))
   :<|> (Named
           '("iput", GuestLinksConfig)
           (Description (FeatureAPIDesc GuestLinksConfig)
            :> (Summary
                  (AppendSymbol "Put config for " (FeatureSymbol GuestLinksConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors GuestLinksConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol GuestLinksConfig
                                                    :> (ReqBody '[JSON] (Feature GuestLinksConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                GuestLinksConfig)))))))))))))
         :<|> Named
                '("ipatch", GuestLinksConfig)
                (Description (FeatureAPIDesc GuestLinksConfig)
                 :> (Summary
                       (AppendSymbol "Patch config for " (FeatureSymbol GuestLinksConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany (FeatureErrors GuestLinksConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol GuestLinksConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  GuestLinksConfig)
                                                             :> Patch
                                                                  '[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]
forall cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", GuestLinksConfig)
     (Description ""
      :> (Summary "Get config for conversationGuestLinks"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("conversationGuestLinks"
                                      :> Get '[JSON] (LockableFeature GuestLinksConfig))))))))))
   :<|> (Named
           '("iput", GuestLinksConfig)
           (Description ""
            :> (Summary "Put config for conversationGuestLinks"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("conversationGuestLinks"
                                                    :> (ReqBody '[JSON] (Feature GuestLinksConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                GuestLinksConfig)))))))))))))
         :<|> Named
                '("ipatch", GuestLinksConfig)
                (Description ""
                 :> (Summary "Patch config for conversationGuestLinks"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("conversationGuestLinks"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  GuestLinksConfig)
                                                             :> Patch
                                                                  '[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
         '("iget", SndFactorPasswordChallengeConfig)
         (Description ""
          :> (Summary "Get config for sndFactorPasswordChallenge"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("sndFactorPasswordChallenge"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SndFactorPasswordChallengeConfig))))))))))
       :<|> (Named
               '("iput", SndFactorPasswordChallengeConfig)
               (Description ""
                :> (Summary "Put config for sndFactorPasswordChallenge"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("sndFactorPasswordChallenge"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature
                                                                 SndFactorPasswordChallengeConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SndFactorPasswordChallengeConfig)))))))))))))
             :<|> Named
                    '("ipatch", SndFactorPasswordChallengeConfig)
                    (Description ""
                     :> (Summary "Patch config for sndFactorPasswordChallenge"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("sndFactorPasswordChallenge"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      SndFactorPasswordChallengeConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SndFactorPasswordChallengeConfig)))))))))))))))
      :<|> ((Named
               '("iget", MLSConfig)
               (Description ""
                :> (Summary "Get config for mls"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("mls"
                                                :> Get '[JSON] (LockableFeature MLSConfig))))))))))
             :<|> (Named
                     '("iput", MLSConfig)
                     (Description ""
                      :> (Summary "Put config for mls"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("mls"
                                                              :> (ReqBody
                                                                    '[JSON] (Feature MLSConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          MLSConfig)))))))))))))
                   :<|> Named
                          '("ipatch", MLSConfig)
                          (Description ""
                           :> (Summary "Patch config for mls"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("mls"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            MLSConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               MLSConfig)))))))))))))))
            :<|> ((Named
                     '("iget", ExposeInvitationURLsToTeamAdminConfig)
                     (Description ""
                      :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              ExposeInvitationURLsToTeamAdminConfig))))))))))
                   :<|> (Named
                           '("iput", ExposeInvitationURLsToTeamAdminConfig)
                           (Description ""
                            :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                         :<|> Named
                                '("ipatch", ExposeInvitationURLsToTeamAdminConfig)
                                (Description ""
                                 :> (Summary "Patch config for exposeInvitationURLsToTeamAdmin"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("exposeInvitationURLsToTeamAdmin"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", OutlookCalIntegrationConfig)
                           (Description ""
                            :> (Summary "Get config for outlookCalIntegration"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("outlookCalIntegration"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    OutlookCalIntegrationConfig))))))))))
                         :<|> (Named
                                 '("iput", OutlookCalIntegrationConfig)
                                 (Description ""
                                  :> (Summary "Put config for outlookCalIntegration"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("outlookCalIntegration"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   OutlookCalIntegrationConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      OutlookCalIntegrationConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", OutlookCalIntegrationConfig)
                                      (Description ""
                                       :> (Summary "Patch config for outlookCalIntegration"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("outlookCalIntegration"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        OutlookCalIntegrationConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           OutlookCalIntegrationConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", MlsE2EIdConfig)
                                 (Description ""
                                  :> (Summary "Get config for mlsE2EId"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("mlsE2EId"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          MlsE2EIdConfig))))))))))
                               :<|> (Named
                                       '("iput", MlsE2EIdConfig)
                                       (Description ""
                                        :> (Summary "Put config for mlsE2EId"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("mlsE2EId"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         MlsE2EIdConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            MlsE2EIdConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", MlsE2EIdConfig)
                                            (Description ""
                                             :> (Summary "Patch config for mlsE2EId"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("mlsE2EId"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              MlsE2EIdConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 MlsE2EIdConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", MlsMigrationConfig)
                                       (Description ""
                                        :> (Summary "Get config for mlsMigration"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("mlsMigration"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                MlsMigrationConfig))))))))))
                                     :<|> (Named
                                             '("iput", MlsMigrationConfig)
                                             (Description ""
                                              :> (Summary "Put config for mlsMigration"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("mlsMigration"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               MlsMigrationConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  MlsMigrationConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", MlsMigrationConfig)
                                                  (Description ""
                                                   :> (Summary "Patch config for mlsMigration"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("mlsMigration"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    MlsMigrationConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       MlsMigrationConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", EnforceFileDownloadLocationConfig)
                                             (Description
                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                              :> (Summary
                                                    "Get config for enforceFileDownloadLocation"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("enforceFileDownloadLocation"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      EnforceFileDownloadLocationConfig))))))))))
                                           :<|> (Named
                                                   '("iput", EnforceFileDownloadLocationConfig)
                                                   (Description
                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                    :> (Summary
                                                          "Put config for enforceFileDownloadLocation"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("enforceFileDownloadLocation"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        EnforceFileDownloadLocationConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch",
                                                          EnforceFileDownloadLocationConfig)
                                                        (Description
                                                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                         :> (Summary
                                                               "Patch config for enforceFileDownloadLocation"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("enforceFileDownloadLocation"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             EnforceFileDownloadLocationConfig)))))))))))))))
                                          :<|> (Named
                                                  '("iget", LimitedEventFanoutConfig)
                                                  (Description ""
                                                   :> (Summary "Get config for limitedEventFanout"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("limitedEventFanout"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           LimitedEventFanoutConfig))))))))))
                                                :<|> (Named
                                                        '("iput", LimitedEventFanoutConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Put config for limitedEventFanout"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("limitedEventFanout"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (Feature
                                                                                                          LimitedEventFanoutConfig)
                                                                                                     :> Put
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             LimitedEventFanoutConfig)))))))))))))
                                                      :<|> Named
                                                             '("ipatch", LimitedEventFanoutConfig)
                                                             (Description ""
                                                              :> (Summary
                                                                    "Patch config for limitedEventFanout"
                                                                  :> (CanThrow
                                                                        ('MissingPermission
                                                                           'Nothing)
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> (CanThrow
                                                                                    TeamFeatureError
                                                                                  :> (CanThrowMany
                                                                                        '[]
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("limitedEventFanout"
                                                                                                      :> (ReqBody
                                                                                                            '[JSON]
                                                                                                            (LockableFeaturePatch
                                                                                                               LimitedEventFanoutConfig)
                                                                                                          :> Patch
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  LimitedEventFanoutConfig))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", GuestLinksConfig)
         (Description ""
          :> (Summary "Get config for conversationGuestLinks"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("conversationGuestLinks"
                                          :> Get '[JSON] (LockableFeature GuestLinksConfig))))))))))
       :<|> (Named
               '("iput", GuestLinksConfig)
               (Description ""
                :> (Summary "Put config for conversationGuestLinks"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("conversationGuestLinks"
                                                        :> (ReqBody
                                                              '[JSON] (Feature GuestLinksConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    GuestLinksConfig)))))))))))))
             :<|> Named
                    '("ipatch", GuestLinksConfig)
                    (Description ""
                     :> (Summary "Patch config for conversationGuestLinks"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("conversationGuestLinks"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      GuestLinksConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         GuestLinksConfig)))))))))))))))
      :<|> ((Named
               '("iget", SndFactorPasswordChallengeConfig)
               (Description ""
                :> (Summary "Get config for sndFactorPasswordChallenge"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("sndFactorPasswordChallenge"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        SndFactorPasswordChallengeConfig))))))))))
             :<|> (Named
                     '("iput", SndFactorPasswordChallengeConfig)
                     (Description ""
                      :> (Summary "Put config for sndFactorPasswordChallenge"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("sndFactorPasswordChallenge"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       SndFactorPasswordChallengeConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          SndFactorPasswordChallengeConfig)))))))))))))
                   :<|> Named
                          '("ipatch", SndFactorPasswordChallengeConfig)
                          (Description ""
                           :> (Summary "Patch config for sndFactorPasswordChallenge"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("sndFactorPasswordChallenge"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            SndFactorPasswordChallengeConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SndFactorPasswordChallengeConfig)))))))))))))))
            :<|> ((Named
                     '("iget", MLSConfig)
                     (Description ""
                      :> (Summary "Get config for mls"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("mls"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature MLSConfig))))))))))
                   :<|> (Named
                           '("iput", MLSConfig)
                           (Description ""
                            :> (Summary "Put config for mls"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("mls"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature MLSConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                MLSConfig)))))))))))))
                         :<|> Named
                                '("ipatch", MLSConfig)
                                (Description ""
                                 :> (Summary "Patch config for mls"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("mls"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  MLSConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     MLSConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", ExposeInvitationURLsToTeamAdminConfig)
                           (Description ""
                            :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    ExposeInvitationURLsToTeamAdminConfig))))))))))
                         :<|> (Named
                                 '("iput", ExposeInvitationURLsToTeamAdminConfig)
                                 (Description ""
                                  :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", ExposeInvitationURLsToTeamAdminConfig)
                                      (Description ""
                                       :> (Summary
                                             "Patch config for exposeInvitationURLsToTeamAdmin"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("exposeInvitationURLsToTeamAdmin"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", OutlookCalIntegrationConfig)
                                 (Description ""
                                  :> (Summary "Get config for outlookCalIntegration"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("outlookCalIntegration"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          OutlookCalIntegrationConfig))))))))))
                               :<|> (Named
                                       '("iput", OutlookCalIntegrationConfig)
                                       (Description ""
                                        :> (Summary "Put config for outlookCalIntegration"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("outlookCalIntegration"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         OutlookCalIntegrationConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            OutlookCalIntegrationConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", OutlookCalIntegrationConfig)
                                            (Description ""
                                             :> (Summary "Patch config for outlookCalIntegration"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("outlookCalIntegration"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              OutlookCalIntegrationConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 OutlookCalIntegrationConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", MlsE2EIdConfig)
                                       (Description ""
                                        :> (Summary "Get config for mlsE2EId"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("mlsE2EId"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                MlsE2EIdConfig))))))))))
                                     :<|> (Named
                                             '("iput", MlsE2EIdConfig)
                                             (Description ""
                                              :> (Summary "Put config for mlsE2EId"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("mlsE2EId"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               MlsE2EIdConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  MlsE2EIdConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", MlsE2EIdConfig)
                                                  (Description ""
                                                   :> (Summary "Patch config for mlsE2EId"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("mlsE2EId"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    MlsE2EIdConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       MlsE2EIdConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", MlsMigrationConfig)
                                             (Description ""
                                              :> (Summary "Get config for mlsMigration"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("mlsMigration"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      MlsMigrationConfig))))))))))
                                           :<|> (Named
                                                   '("iput", MlsMigrationConfig)
                                                   (Description ""
                                                    :> (Summary "Put config for mlsMigration"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mlsMigration"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     MlsMigrationConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        MlsMigrationConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch", MlsMigrationConfig)
                                                        (Description ""
                                                         :> (Summary "Patch config for mlsMigration"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("mlsMigration"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          MlsMigrationConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             MlsMigrationConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("iget", EnforceFileDownloadLocationConfig)
                                                   (Description
                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                    :> (Summary
                                                          "Get config for enforceFileDownloadLocation"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("enforceFileDownloadLocation"
                                                                                    :> Get
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            EnforceFileDownloadLocationConfig))))))))))
                                                 :<|> (Named
                                                         '("iput",
                                                           EnforceFileDownloadLocationConfig)
                                                         (Description
                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                          :> (Summary
                                                                "Put config for enforceFileDownloadLocation"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (Feature
                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                      :> Put
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              EnforceFileDownloadLocationConfig)))))))))))))
                                                       :<|> Named
                                                              '("ipatch",
                                                                EnforceFileDownloadLocationConfig)
                                                              (Description
                                                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                               :> (Summary
                                                                     "Patch config for enforceFileDownloadLocation"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("enforceFileDownloadLocation"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (LockableFeaturePatch
                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                           :> Patch
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   EnforceFileDownloadLocationConfig)))))))))))))))
                                                :<|> (Named
                                                        '("iget", LimitedEventFanoutConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Get config for limitedEventFanout"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("limitedEventFanout"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 LimitedEventFanoutConfig))))))))))
                                                      :<|> (Named
                                                              '("iput", LimitedEventFanoutConfig)
                                                              (Description ""
                                                               :> (Summary
                                                                     "Put config for limitedEventFanout"
                                                                   :> (CanThrow
                                                                         ('MissingPermission
                                                                            'Nothing)
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     TeamFeatureError
                                                                                   :> (CanThrowMany
                                                                                         '[]
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("limitedEventFanout"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             (Feature
                                                                                                                LimitedEventFanoutConfig)
                                                                                                           :> Put
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   LimitedEventFanoutConfig)))))))))))))
                                                            :<|> Named
                                                                   '("ipatch",
                                                                     LimitedEventFanoutConfig)
                                                                   (Description ""
                                                                    :> (Summary
                                                                          "Patch config for limitedEventFanout"
                                                                        :> (CanThrow
                                                                              ('MissingPermission
                                                                                 'Nothing)
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> (CanThrow
                                                                                          TeamFeatureError
                                                                                        :> (CanThrowMany
                                                                                              '[]
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("limitedEventFanout"
                                                                                                            :> (ReqBody
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeaturePatch
                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                :> Patch
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        LimitedEventFanoutConfig)))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", SndFactorPasswordChallengeConfig)
     (Description ""
      :> (Summary "Get config for sndFactorPasswordChallenge"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("sndFactorPasswordChallenge"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature
                                              SndFactorPasswordChallengeConfig))))))))))
   :<|> (Named
           '("iput", SndFactorPasswordChallengeConfig)
           (Description ""
            :> (Summary "Put config for sndFactorPasswordChallenge"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("sndFactorPasswordChallenge"
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature SndFactorPasswordChallengeConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                SndFactorPasswordChallengeConfig)))))))))))))
         :<|> Named
                '("ipatch", SndFactorPasswordChallengeConfig)
                (Description ""
                 :> (Summary "Patch config for sndFactorPasswordChallenge"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("sndFactorPasswordChallenge"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  SndFactorPasswordChallengeConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SndFactorPasswordChallengeConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", SndFactorPasswordChallengeConfig)
     (Description (FeatureAPIDesc SndFactorPasswordChallengeConfig)
      :> (Summary
            (AppendSymbol
               "Get config for " (FeatureSymbol SndFactorPasswordChallengeConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol SndFactorPasswordChallengeConfig
                                      :> Get
                                           '[JSON]
                                           (LockableFeature
                                              SndFactorPasswordChallengeConfig))))))))))
   :<|> (Named
           '("iput", SndFactorPasswordChallengeConfig)
           (Description (FeatureAPIDesc SndFactorPasswordChallengeConfig)
            :> (Summary
                  (AppendSymbol
                     "Put config for " (FeatureSymbol SndFactorPasswordChallengeConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors SndFactorPasswordChallengeConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol SndFactorPasswordChallengeConfig
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature SndFactorPasswordChallengeConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                SndFactorPasswordChallengeConfig)))))))))))))
         :<|> Named
                '("ipatch", SndFactorPasswordChallengeConfig)
                (Description (FeatureAPIDesc SndFactorPasswordChallengeConfig)
                 :> (Summary
                       (AppendSymbol
                          "Patch config for "
                          (FeatureSymbol SndFactorPasswordChallengeConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany
                                           (FeatureErrors SndFactorPasswordChallengeConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol
                                                           SndFactorPasswordChallengeConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  SndFactorPasswordChallengeConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SndFactorPasswordChallengeConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", SndFactorPasswordChallengeConfig)
     (Description ""
      :> (Summary "Get config for sndFactorPasswordChallenge"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("sndFactorPasswordChallenge"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature
                                              SndFactorPasswordChallengeConfig))))))))))
   :<|> (Named
           '("iput", SndFactorPasswordChallengeConfig)
           (Description ""
            :> (Summary "Put config for sndFactorPasswordChallenge"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("sndFactorPasswordChallenge"
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature SndFactorPasswordChallengeConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                SndFactorPasswordChallengeConfig)))))))))))))
         :<|> Named
                '("ipatch", SndFactorPasswordChallengeConfig)
                (Description ""
                 :> (Summary "Patch config for sndFactorPasswordChallenge"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("sndFactorPasswordChallenge"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  SndFactorPasswordChallengeConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SndFactorPasswordChallengeConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", MLSConfig)
         (Description ""
          :> (Summary "Get config for mls"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("mls" :> Get '[JSON] (LockableFeature MLSConfig))))))))))
       :<|> (Named
               '("iput", MLSConfig)
               (Description ""
                :> (Summary "Put config for mls"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("mls"
                                                        :> (ReqBody '[JSON] (Feature MLSConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    MLSConfig)))))))))))))
             :<|> Named
                    '("ipatch", MLSConfig)
                    (Description ""
                     :> (Summary "Patch config for mls"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("mls"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch MLSConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         MLSConfig)))))))))))))))
      :<|> ((Named
               '("iget", ExposeInvitationURLsToTeamAdminConfig)
               (Description ""
                :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        ExposeInvitationURLsToTeamAdminConfig))))))))))
             :<|> (Named
                     '("iput", ExposeInvitationURLsToTeamAdminConfig)
                     (Description ""
                      :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                   :<|> Named
                          '("ipatch", ExposeInvitationURLsToTeamAdminConfig)
                          (Description ""
                           :> (Summary "Patch config for exposeInvitationURLsToTeamAdmin"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("exposeInvitationURLsToTeamAdmin"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
            :<|> ((Named
                     '("iget", OutlookCalIntegrationConfig)
                     (Description ""
                      :> (Summary "Get config for outlookCalIntegration"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("outlookCalIntegration"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              OutlookCalIntegrationConfig))))))))))
                   :<|> (Named
                           '("iput", OutlookCalIntegrationConfig)
                           (Description ""
                            :> (Summary "Put config for outlookCalIntegration"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("outlookCalIntegration"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             OutlookCalIntegrationConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                OutlookCalIntegrationConfig)))))))))))))
                         :<|> Named
                                '("ipatch", OutlookCalIntegrationConfig)
                                (Description ""
                                 :> (Summary "Patch config for outlookCalIntegration"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("outlookCalIntegration"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  OutlookCalIntegrationConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     OutlookCalIntegrationConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", MlsE2EIdConfig)
                           (Description ""
                            :> (Summary "Get config for mlsE2EId"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("mlsE2EId"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    MlsE2EIdConfig))))))))))
                         :<|> (Named
                                 '("iput", MlsE2EIdConfig)
                                 (Description ""
                                  :> (Summary "Put config for mlsE2EId"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("mlsE2EId"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   MlsE2EIdConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      MlsE2EIdConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", MlsE2EIdConfig)
                                      (Description ""
                                       :> (Summary "Patch config for mlsE2EId"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("mlsE2EId"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        MlsE2EIdConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           MlsE2EIdConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", MlsMigrationConfig)
                                 (Description ""
                                  :> (Summary "Get config for mlsMigration"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("mlsMigration"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          MlsMigrationConfig))))))))))
                               :<|> (Named
                                       '("iput", MlsMigrationConfig)
                                       (Description ""
                                        :> (Summary "Put config for mlsMigration"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("mlsMigration"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         MlsMigrationConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            MlsMigrationConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", MlsMigrationConfig)
                                            (Description ""
                                             :> (Summary "Patch config for mlsMigration"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("mlsMigration"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              MlsMigrationConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 MlsMigrationConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", EnforceFileDownloadLocationConfig)
                                       (Description
                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                        :> (Summary "Get config for enforceFileDownloadLocation"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("enforceFileDownloadLocation"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                EnforceFileDownloadLocationConfig))))))))))
                                     :<|> (Named
                                             '("iput", EnforceFileDownloadLocationConfig)
                                             (Description
                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                              :> (Summary
                                                    "Put config for enforceFileDownloadLocation"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("enforceFileDownloadLocation"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               EnforceFileDownloadLocationConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  EnforceFileDownloadLocationConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", EnforceFileDownloadLocationConfig)
                                                  (Description
                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                   :> (Summary
                                                         "Patch config for enforceFileDownloadLocation"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("enforceFileDownloadLocation"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       EnforceFileDownloadLocationConfig)))))))))))))))
                                    :<|> (Named
                                            '("iget", LimitedEventFanoutConfig)
                                            (Description ""
                                             :> (Summary "Get config for limitedEventFanout"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("limitedEventFanout"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     LimitedEventFanoutConfig))))))))))
                                          :<|> (Named
                                                  '("iput", LimitedEventFanoutConfig)
                                                  (Description ""
                                                   :> (Summary "Put config for limitedEventFanout"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("limitedEventFanout"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (Feature
                                                                                                    LimitedEventFanoutConfig)
                                                                                               :> Put
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       LimitedEventFanoutConfig)))))))))))))
                                                :<|> Named
                                                       '("ipatch", LimitedEventFanoutConfig)
                                                       (Description ""
                                                        :> (Summary
                                                              "Patch config for limitedEventFanout"
                                                            :> (CanThrow
                                                                  ('MissingPermission 'Nothing)
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> (CanThrow
                                                                              TeamFeatureError
                                                                            :> (CanThrowMany '[]
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("limitedEventFanout"
                                                                                                :> (ReqBody
                                                                                                      '[JSON]
                                                                                                      (LockableFeaturePatch
                                                                                                         LimitedEventFanoutConfig)
                                                                                                    :> Patch
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            LimitedEventFanoutConfig)))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", SndFactorPasswordChallengeConfig)
         (Description ""
          :> (Summary "Get config for sndFactorPasswordChallenge"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("sndFactorPasswordChallenge"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SndFactorPasswordChallengeConfig))))))))))
       :<|> (Named
               '("iput", SndFactorPasswordChallengeConfig)
               (Description ""
                :> (Summary "Put config for sndFactorPasswordChallenge"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("sndFactorPasswordChallenge"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature
                                                                 SndFactorPasswordChallengeConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SndFactorPasswordChallengeConfig)))))))))))))
             :<|> Named
                    '("ipatch", SndFactorPasswordChallengeConfig)
                    (Description ""
                     :> (Summary "Patch config for sndFactorPasswordChallenge"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("sndFactorPasswordChallenge"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      SndFactorPasswordChallengeConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SndFactorPasswordChallengeConfig)))))))))))))))
      :<|> ((Named
               '("iget", MLSConfig)
               (Description ""
                :> (Summary "Get config for mls"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("mls"
                                                :> Get '[JSON] (LockableFeature MLSConfig))))))))))
             :<|> (Named
                     '("iput", MLSConfig)
                     (Description ""
                      :> (Summary "Put config for mls"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("mls"
                                                              :> (ReqBody
                                                                    '[JSON] (Feature MLSConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          MLSConfig)))))))))))))
                   :<|> Named
                          '("ipatch", MLSConfig)
                          (Description ""
                           :> (Summary "Patch config for mls"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("mls"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            MLSConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               MLSConfig)))))))))))))))
            :<|> ((Named
                     '("iget", ExposeInvitationURLsToTeamAdminConfig)
                     (Description ""
                      :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              ExposeInvitationURLsToTeamAdminConfig))))))))))
                   :<|> (Named
                           '("iput", ExposeInvitationURLsToTeamAdminConfig)
                           (Description ""
                            :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                         :<|> Named
                                '("ipatch", ExposeInvitationURLsToTeamAdminConfig)
                                (Description ""
                                 :> (Summary "Patch config for exposeInvitationURLsToTeamAdmin"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("exposeInvitationURLsToTeamAdmin"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", OutlookCalIntegrationConfig)
                           (Description ""
                            :> (Summary "Get config for outlookCalIntegration"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("outlookCalIntegration"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    OutlookCalIntegrationConfig))))))))))
                         :<|> (Named
                                 '("iput", OutlookCalIntegrationConfig)
                                 (Description ""
                                  :> (Summary "Put config for outlookCalIntegration"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("outlookCalIntegration"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   OutlookCalIntegrationConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      OutlookCalIntegrationConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", OutlookCalIntegrationConfig)
                                      (Description ""
                                       :> (Summary "Patch config for outlookCalIntegration"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("outlookCalIntegration"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        OutlookCalIntegrationConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           OutlookCalIntegrationConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", MlsE2EIdConfig)
                                 (Description ""
                                  :> (Summary "Get config for mlsE2EId"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("mlsE2EId"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          MlsE2EIdConfig))))))))))
                               :<|> (Named
                                       '("iput", MlsE2EIdConfig)
                                       (Description ""
                                        :> (Summary "Put config for mlsE2EId"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("mlsE2EId"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         MlsE2EIdConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            MlsE2EIdConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", MlsE2EIdConfig)
                                            (Description ""
                                             :> (Summary "Patch config for mlsE2EId"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("mlsE2EId"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              MlsE2EIdConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 MlsE2EIdConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", MlsMigrationConfig)
                                       (Description ""
                                        :> (Summary "Get config for mlsMigration"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("mlsMigration"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                MlsMigrationConfig))))))))))
                                     :<|> (Named
                                             '("iput", MlsMigrationConfig)
                                             (Description ""
                                              :> (Summary "Put config for mlsMigration"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("mlsMigration"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               MlsMigrationConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  MlsMigrationConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", MlsMigrationConfig)
                                                  (Description ""
                                                   :> (Summary "Patch config for mlsMigration"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("mlsMigration"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    MlsMigrationConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       MlsMigrationConfig)))))))))))))))
                                    :<|> ((Named
                                             '("iget", EnforceFileDownloadLocationConfig)
                                             (Description
                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                              :> (Summary
                                                    "Get config for enforceFileDownloadLocation"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("enforceFileDownloadLocation"
                                                                              :> Get
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      EnforceFileDownloadLocationConfig))))))))))
                                           :<|> (Named
                                                   '("iput", EnforceFileDownloadLocationConfig)
                                                   (Description
                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                    :> (Summary
                                                          "Put config for enforceFileDownloadLocation"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("enforceFileDownloadLocation"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (Feature
                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                :> Put
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        EnforceFileDownloadLocationConfig)))))))))))))
                                                 :<|> Named
                                                        '("ipatch",
                                                          EnforceFileDownloadLocationConfig)
                                                        (Description
                                                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                         :> (Summary
                                                               "Patch config for enforceFileDownloadLocation"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("enforceFileDownloadLocation"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (LockableFeaturePatch
                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                     :> Patch
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             EnforceFileDownloadLocationConfig)))))))))))))))
                                          :<|> (Named
                                                  '("iget", LimitedEventFanoutConfig)
                                                  (Description ""
                                                   :> (Summary "Get config for limitedEventFanout"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("limitedEventFanout"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           LimitedEventFanoutConfig))))))))))
                                                :<|> (Named
                                                        '("iput", LimitedEventFanoutConfig)
                                                        (Description ""
                                                         :> (Summary
                                                               "Put config for limitedEventFanout"
                                                             :> (CanThrow
                                                                   ('MissingPermission 'Nothing)
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               TeamFeatureError
                                                                             :> (CanThrowMany '[]
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("limitedEventFanout"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       (Feature
                                                                                                          LimitedEventFanoutConfig)
                                                                                                     :> Put
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             LimitedEventFanoutConfig)))))))))))))
                                                      :<|> Named
                                                             '("ipatch", LimitedEventFanoutConfig)
                                                             (Description ""
                                                              :> (Summary
                                                                    "Patch config for limitedEventFanout"
                                                                  :> (CanThrow
                                                                        ('MissingPermission
                                                                           'Nothing)
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> (CanThrow
                                                                                    TeamFeatureError
                                                                                  :> (CanThrowMany
                                                                                        '[]
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("limitedEventFanout"
                                                                                                      :> (ReqBody
                                                                                                            '[JSON]
                                                                                                            (LockableFeaturePatch
                                                                                                               LimitedEventFanoutConfig)
                                                                                                          :> Patch
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  LimitedEventFanoutConfig))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", MLSConfig)
     (Description ""
      :> (Summary "Get config for mls"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("mls" :> Get '[JSON] (LockableFeature MLSConfig))))))))))
   :<|> (Named
           '("iput", MLSConfig)
           (Description ""
            :> (Summary "Put config for mls"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("mls"
                                                    :> (ReqBody '[JSON] (Feature MLSConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature MLSConfig)))))))))))))
         :<|> Named
                '("ipatch", MLSConfig)
                (Description ""
                 :> (Summary "Patch config for mls"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("mls"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch MLSConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     MLSConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", MLSConfig)
     (Description (FeatureAPIDesc MLSConfig)
      :> (Summary
            (AppendSymbol "Get config for " (FeatureSymbol MLSConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol MLSConfig
                                      :> Get '[JSON] (LockableFeature MLSConfig))))))))))
   :<|> (Named
           '("iput", MLSConfig)
           (Description (FeatureAPIDesc MLSConfig)
            :> (Summary
                  (AppendSymbol "Put config for " (FeatureSymbol MLSConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors MLSConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol MLSConfig
                                                    :> (ReqBody '[JSON] (Feature MLSConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature MLSConfig)))))))))))))
         :<|> Named
                '("ipatch", MLSConfig)
                (Description (FeatureAPIDesc MLSConfig)
                 :> (Summary
                       (AppendSymbol "Patch config for " (FeatureSymbol MLSConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany (FeatureErrors MLSConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol MLSConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch MLSConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     MLSConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", MLSConfig)
     (Description ""
      :> (Summary "Get config for mls"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("mls" :> Get '[JSON] (LockableFeature MLSConfig))))))))))
   :<|> (Named
           '("iput", MLSConfig)
           (Description ""
            :> (Summary "Put config for mls"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("mls"
                                                    :> (ReqBody '[JSON] (Feature MLSConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature MLSConfig)))))))))))))
         :<|> Named
                '("ipatch", MLSConfig)
                (Description ""
                 :> (Summary "Patch config for mls"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("mls"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch MLSConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     MLSConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", ExposeInvitationURLsToTeamAdminConfig)
         (Description ""
          :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("exposeInvitationURLsToTeamAdmin"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  ExposeInvitationURLsToTeamAdminConfig))))))))))
       :<|> (Named
               '("iput", ExposeInvitationURLsToTeamAdminConfig)
               (Description ""
                :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("exposeInvitationURLsToTeamAdmin"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature
                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    ExposeInvitationURLsToTeamAdminConfig)))))))))))))
             :<|> Named
                    '("ipatch", ExposeInvitationURLsToTeamAdminConfig)
                    (Description ""
                     :> (Summary "Patch config for exposeInvitationURLsToTeamAdmin"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("exposeInvitationURLsToTeamAdmin"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
      :<|> ((Named
               '("iget", OutlookCalIntegrationConfig)
               (Description ""
                :> (Summary "Get config for outlookCalIntegration"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("outlookCalIntegration"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        OutlookCalIntegrationConfig))))))))))
             :<|> (Named
                     '("iput", OutlookCalIntegrationConfig)
                     (Description ""
                      :> (Summary "Put config for outlookCalIntegration"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("outlookCalIntegration"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       OutlookCalIntegrationConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          OutlookCalIntegrationConfig)))))))))))))
                   :<|> Named
                          '("ipatch", OutlookCalIntegrationConfig)
                          (Description ""
                           :> (Summary "Patch config for outlookCalIntegration"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("outlookCalIntegration"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            OutlookCalIntegrationConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               OutlookCalIntegrationConfig)))))))))))))))
            :<|> ((Named
                     '("iget", MlsE2EIdConfig)
                     (Description ""
                      :> (Summary "Get config for mlsE2EId"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("mlsE2EId"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature MlsE2EIdConfig))))))))))
                   :<|> (Named
                           '("iput", MlsE2EIdConfig)
                           (Description ""
                            :> (Summary "Put config for mlsE2EId"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("mlsE2EId"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature MlsE2EIdConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                MlsE2EIdConfig)))))))))))))
                         :<|> Named
                                '("ipatch", MlsE2EIdConfig)
                                (Description ""
                                 :> (Summary "Patch config for mlsE2EId"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("mlsE2EId"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  MlsE2EIdConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     MlsE2EIdConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", MlsMigrationConfig)
                           (Description ""
                            :> (Summary "Get config for mlsMigration"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("mlsMigration"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    MlsMigrationConfig))))))))))
                         :<|> (Named
                                 '("iput", MlsMigrationConfig)
                                 (Description ""
                                  :> (Summary "Put config for mlsMigration"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("mlsMigration"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   MlsMigrationConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      MlsMigrationConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", MlsMigrationConfig)
                                      (Description ""
                                       :> (Summary "Patch config for mlsMigration"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("mlsMigration"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        MlsMigrationConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           MlsMigrationConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", EnforceFileDownloadLocationConfig)
                                 (Description
                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                  :> (Summary "Get config for enforceFileDownloadLocation"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("enforceFileDownloadLocation"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          EnforceFileDownloadLocationConfig))))))))))
                               :<|> (Named
                                       '("iput", EnforceFileDownloadLocationConfig)
                                       (Description
                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                        :> (Summary "Put config for enforceFileDownloadLocation"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("enforceFileDownloadLocation"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         EnforceFileDownloadLocationConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            EnforceFileDownloadLocationConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", EnforceFileDownloadLocationConfig)
                                            (Description
                                               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                             :> (Summary
                                                   "Patch config for enforceFileDownloadLocation"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("enforceFileDownloadLocation"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              EnforceFileDownloadLocationConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 EnforceFileDownloadLocationConfig)))))))))))))))
                              :<|> (Named
                                      '("iget", LimitedEventFanoutConfig)
                                      (Description ""
                                       :> (Summary "Get config for limitedEventFanout"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("limitedEventFanout"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               LimitedEventFanoutConfig))))))))))
                                    :<|> (Named
                                            '("iput", LimitedEventFanoutConfig)
                                            (Description ""
                                             :> (Summary "Put config for limitedEventFanout"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("limitedEventFanout"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (Feature
                                                                                              LimitedEventFanoutConfig)
                                                                                         :> Put
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 LimitedEventFanoutConfig)))))))))))))
                                          :<|> Named
                                                 '("ipatch", LimitedEventFanoutConfig)
                                                 (Description ""
                                                  :> (Summary "Patch config for limitedEventFanout"
                                                      :> (CanThrow ('MissingPermission 'Nothing)
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> (CanThrow TeamFeatureError
                                                                      :> (CanThrowMany '[]
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("limitedEventFanout"
                                                                                          :> (ReqBody
                                                                                                '[JSON]
                                                                                                (LockableFeaturePatch
                                                                                                   LimitedEventFanoutConfig)
                                                                                              :> Patch
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      LimitedEventFanoutConfig))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", MLSConfig)
         (Description ""
          :> (Summary "Get config for mls"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("mls" :> Get '[JSON] (LockableFeature MLSConfig))))))))))
       :<|> (Named
               '("iput", MLSConfig)
               (Description ""
                :> (Summary "Put config for mls"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("mls"
                                                        :> (ReqBody '[JSON] (Feature MLSConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    MLSConfig)))))))))))))
             :<|> Named
                    '("ipatch", MLSConfig)
                    (Description ""
                     :> (Summary "Patch config for mls"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("mls"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch MLSConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         MLSConfig)))))))))))))))
      :<|> ((Named
               '("iget", ExposeInvitationURLsToTeamAdminConfig)
               (Description ""
                :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        ExposeInvitationURLsToTeamAdminConfig))))))))))
             :<|> (Named
                     '("iput", ExposeInvitationURLsToTeamAdminConfig)
                     (Description ""
                      :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                   :<|> Named
                          '("ipatch", ExposeInvitationURLsToTeamAdminConfig)
                          (Description ""
                           :> (Summary "Patch config for exposeInvitationURLsToTeamAdmin"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("exposeInvitationURLsToTeamAdmin"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
            :<|> ((Named
                     '("iget", OutlookCalIntegrationConfig)
                     (Description ""
                      :> (Summary "Get config for outlookCalIntegration"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("outlookCalIntegration"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              OutlookCalIntegrationConfig))))))))))
                   :<|> (Named
                           '("iput", OutlookCalIntegrationConfig)
                           (Description ""
                            :> (Summary "Put config for outlookCalIntegration"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("outlookCalIntegration"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             OutlookCalIntegrationConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                OutlookCalIntegrationConfig)))))))))))))
                         :<|> Named
                                '("ipatch", OutlookCalIntegrationConfig)
                                (Description ""
                                 :> (Summary "Patch config for outlookCalIntegration"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("outlookCalIntegration"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  OutlookCalIntegrationConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     OutlookCalIntegrationConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", MlsE2EIdConfig)
                           (Description ""
                            :> (Summary "Get config for mlsE2EId"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("mlsE2EId"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    MlsE2EIdConfig))))))))))
                         :<|> (Named
                                 '("iput", MlsE2EIdConfig)
                                 (Description ""
                                  :> (Summary "Put config for mlsE2EId"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("mlsE2EId"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   MlsE2EIdConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      MlsE2EIdConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", MlsE2EIdConfig)
                                      (Description ""
                                       :> (Summary "Patch config for mlsE2EId"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("mlsE2EId"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        MlsE2EIdConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           MlsE2EIdConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", MlsMigrationConfig)
                                 (Description ""
                                  :> (Summary "Get config for mlsMigration"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("mlsMigration"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          MlsMigrationConfig))))))))))
                               :<|> (Named
                                       '("iput", MlsMigrationConfig)
                                       (Description ""
                                        :> (Summary "Put config for mlsMigration"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("mlsMigration"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         MlsMigrationConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            MlsMigrationConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", MlsMigrationConfig)
                                            (Description ""
                                             :> (Summary "Patch config for mlsMigration"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("mlsMigration"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              MlsMigrationConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 MlsMigrationConfig)))))))))))))))
                              :<|> ((Named
                                       '("iget", EnforceFileDownloadLocationConfig)
                                       (Description
                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                        :> (Summary "Get config for enforceFileDownloadLocation"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("enforceFileDownloadLocation"
                                                                        :> Get
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                EnforceFileDownloadLocationConfig))))))))))
                                     :<|> (Named
                                             '("iput", EnforceFileDownloadLocationConfig)
                                             (Description
                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                              :> (Summary
                                                    "Put config for enforceFileDownloadLocation"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("enforceFileDownloadLocation"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (Feature
                                                                                               EnforceFileDownloadLocationConfig)
                                                                                          :> Put
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  EnforceFileDownloadLocationConfig)))))))))))))
                                           :<|> Named
                                                  '("ipatch", EnforceFileDownloadLocationConfig)
                                                  (Description
                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                   :> (Summary
                                                         "Patch config for enforceFileDownloadLocation"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("enforceFileDownloadLocation"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (LockableFeaturePatch
                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                               :> Patch
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       EnforceFileDownloadLocationConfig)))))))))))))))
                                    :<|> (Named
                                            '("iget", LimitedEventFanoutConfig)
                                            (Description ""
                                             :> (Summary "Get config for limitedEventFanout"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("limitedEventFanout"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     LimitedEventFanoutConfig))))))))))
                                          :<|> (Named
                                                  '("iput", LimitedEventFanoutConfig)
                                                  (Description ""
                                                   :> (Summary "Put config for limitedEventFanout"
                                                       :> (CanThrow ('MissingPermission 'Nothing)
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow TeamFeatureError
                                                                       :> (CanThrowMany '[]
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("limitedEventFanout"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 (Feature
                                                                                                    LimitedEventFanoutConfig)
                                                                                               :> Put
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       LimitedEventFanoutConfig)))))))))))))
                                                :<|> Named
                                                       '("ipatch", LimitedEventFanoutConfig)
                                                       (Description ""
                                                        :> (Summary
                                                              "Patch config for limitedEventFanout"
                                                            :> (CanThrow
                                                                  ('MissingPermission 'Nothing)
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> (CanThrow
                                                                              TeamFeatureError
                                                                            :> (CanThrowMany '[]
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("limitedEventFanout"
                                                                                                :> (ReqBody
                                                                                                      '[JSON]
                                                                                                      (LockableFeaturePatch
                                                                                                         LimitedEventFanoutConfig)
                                                                                                    :> Patch
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            LimitedEventFanoutConfig)))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", ExposeInvitationURLsToTeamAdminConfig)
     (Description ""
      :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("exposeInvitationURLsToTeamAdmin"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature
                                              ExposeInvitationURLsToTeamAdminConfig))))))))))
   :<|> (Named
           '("iput", ExposeInvitationURLsToTeamAdminConfig)
           (Description ""
            :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature
                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                ExposeInvitationURLsToTeamAdminConfig)))))))))))))
         :<|> Named
                '("ipatch", ExposeInvitationURLsToTeamAdminConfig)
                (Description ""
                 :> (Summary "Patch config for exposeInvitationURLsToTeamAdmin"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("exposeInvitationURLsToTeamAdmin"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", ExposeInvitationURLsToTeamAdminConfig)
     (Description (FeatureAPIDesc ExposeInvitationURLsToTeamAdminConfig)
      :> (Summary
            (AppendSymbol
               "Get config for "
               (FeatureSymbol ExposeInvitationURLsToTeamAdminConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol ExposeInvitationURLsToTeamAdminConfig
                                      :> Get
                                           '[JSON]
                                           (LockableFeature
                                              ExposeInvitationURLsToTeamAdminConfig))))))))))
   :<|> (Named
           '("iput", ExposeInvitationURLsToTeamAdminConfig)
           (Description (FeatureAPIDesc ExposeInvitationURLsToTeamAdminConfig)
            :> (Summary
                  (AppendSymbol
                     "Put config for "
                     (FeatureSymbol ExposeInvitationURLsToTeamAdminConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany
                                      (FeatureErrors ExposeInvitationURLsToTeamAdminConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol
                                                      ExposeInvitationURLsToTeamAdminConfig
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature
                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                ExposeInvitationURLsToTeamAdminConfig)))))))))))))
         :<|> Named
                '("ipatch", ExposeInvitationURLsToTeamAdminConfig)
                (Description (FeatureAPIDesc ExposeInvitationURLsToTeamAdminConfig)
                 :> (Summary
                       (AppendSymbol
                          "Patch config for "
                          (FeatureSymbol ExposeInvitationURLsToTeamAdminConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany
                                           (FeatureErrors ExposeInvitationURLsToTeamAdminConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol
                                                           ExposeInvitationURLsToTeamAdminConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", ExposeInvitationURLsToTeamAdminConfig)
     (Description ""
      :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("exposeInvitationURLsToTeamAdmin"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature
                                              ExposeInvitationURLsToTeamAdminConfig))))))))))
   :<|> (Named
           '("iput", ExposeInvitationURLsToTeamAdminConfig)
           (Description ""
            :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature
                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                ExposeInvitationURLsToTeamAdminConfig)))))))))))))
         :<|> Named
                '("ipatch", ExposeInvitationURLsToTeamAdminConfig)
                (Description ""
                 :> (Summary "Patch config for exposeInvitationURLsToTeamAdmin"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("exposeInvitationURLsToTeamAdmin"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", OutlookCalIntegrationConfig)
         (Description ""
          :> (Summary "Get config for outlookCalIntegration"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("outlookCalIntegration"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  OutlookCalIntegrationConfig))))))))))
       :<|> (Named
               '("iput", OutlookCalIntegrationConfig)
               (Description ""
                :> (Summary "Put config for outlookCalIntegration"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("outlookCalIntegration"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature OutlookCalIntegrationConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    OutlookCalIntegrationConfig)))))))))))))
             :<|> Named
                    '("ipatch", OutlookCalIntegrationConfig)
                    (Description ""
                     :> (Summary "Patch config for outlookCalIntegration"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("outlookCalIntegration"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      OutlookCalIntegrationConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         OutlookCalIntegrationConfig)))))))))))))))
      :<|> ((Named
               '("iget", MlsE2EIdConfig)
               (Description ""
                :> (Summary "Get config for mlsE2EId"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("mlsE2EId"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature MlsE2EIdConfig))))))))))
             :<|> (Named
                     '("iput", MlsE2EIdConfig)
                     (Description ""
                      :> (Summary "Put config for mlsE2EId"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("mlsE2EId"
                                                              :> (ReqBody
                                                                    '[JSON] (Feature MlsE2EIdConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          MlsE2EIdConfig)))))))))))))
                   :<|> Named
                          '("ipatch", MlsE2EIdConfig)
                          (Description ""
                           :> (Summary "Patch config for mlsE2EId"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("mlsE2EId"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            MlsE2EIdConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               MlsE2EIdConfig)))))))))))))))
            :<|> ((Named
                     '("iget", MlsMigrationConfig)
                     (Description ""
                      :> (Summary "Get config for mlsMigration"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("mlsMigration"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              MlsMigrationConfig))))))))))
                   :<|> (Named
                           '("iput", MlsMigrationConfig)
                           (Description ""
                            :> (Summary "Put config for mlsMigration"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("mlsMigration"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             MlsMigrationConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                MlsMigrationConfig)))))))))))))
                         :<|> Named
                                '("ipatch", MlsMigrationConfig)
                                (Description ""
                                 :> (Summary "Patch config for mlsMigration"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("mlsMigration"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  MlsMigrationConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     MlsMigrationConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", EnforceFileDownloadLocationConfig)
                           (Description
                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                            :> (Summary "Get config for enforceFileDownloadLocation"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("enforceFileDownloadLocation"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    EnforceFileDownloadLocationConfig))))))))))
                         :<|> (Named
                                 '("iput", EnforceFileDownloadLocationConfig)
                                 (Description
                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                  :> (Summary "Put config for enforceFileDownloadLocation"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("enforceFileDownloadLocation"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   EnforceFileDownloadLocationConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      EnforceFileDownloadLocationConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", EnforceFileDownloadLocationConfig)
                                      (Description
                                         "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                       :> (Summary "Patch config for enforceFileDownloadLocation"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("enforceFileDownloadLocation"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        EnforceFileDownloadLocationConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           EnforceFileDownloadLocationConfig)))))))))))))))
                        :<|> (Named
                                '("iget", LimitedEventFanoutConfig)
                                (Description ""
                                 :> (Summary "Get config for limitedEventFanout"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("limitedEventFanout"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         LimitedEventFanoutConfig))))))))))
                              :<|> (Named
                                      '("iput", LimitedEventFanoutConfig)
                                      (Description ""
                                       :> (Summary "Put config for limitedEventFanout"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("limitedEventFanout"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (Feature
                                                                                        LimitedEventFanoutConfig)
                                                                                   :> Put
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           LimitedEventFanoutConfig)))))))))))))
                                    :<|> Named
                                           '("ipatch", LimitedEventFanoutConfig)
                                           (Description ""
                                            :> (Summary "Patch config for limitedEventFanout"
                                                :> (CanThrow ('MissingPermission 'Nothing)
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> (CanThrow TeamFeatureError
                                                                :> (CanThrowMany '[]
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("limitedEventFanout"
                                                                                    :> (ReqBody
                                                                                          '[JSON]
                                                                                          (LockableFeaturePatch
                                                                                             LimitedEventFanoutConfig)
                                                                                        :> Patch
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                LimitedEventFanoutConfig)))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", ExposeInvitationURLsToTeamAdminConfig)
         (Description ""
          :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("exposeInvitationURLsToTeamAdmin"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  ExposeInvitationURLsToTeamAdminConfig))))))))))
       :<|> (Named
               '("iput", ExposeInvitationURLsToTeamAdminConfig)
               (Description ""
                :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("exposeInvitationURLsToTeamAdmin"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature
                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    ExposeInvitationURLsToTeamAdminConfig)))))))))))))
             :<|> Named
                    '("ipatch", ExposeInvitationURLsToTeamAdminConfig)
                    (Description ""
                     :> (Summary "Patch config for exposeInvitationURLsToTeamAdmin"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("exposeInvitationURLsToTeamAdmin"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
      :<|> ((Named
               '("iget", OutlookCalIntegrationConfig)
               (Description ""
                :> (Summary "Get config for outlookCalIntegration"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("outlookCalIntegration"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        OutlookCalIntegrationConfig))))))))))
             :<|> (Named
                     '("iput", OutlookCalIntegrationConfig)
                     (Description ""
                      :> (Summary "Put config for outlookCalIntegration"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("outlookCalIntegration"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       OutlookCalIntegrationConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          OutlookCalIntegrationConfig)))))))))))))
                   :<|> Named
                          '("ipatch", OutlookCalIntegrationConfig)
                          (Description ""
                           :> (Summary "Patch config for outlookCalIntegration"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("outlookCalIntegration"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            OutlookCalIntegrationConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               OutlookCalIntegrationConfig)))))))))))))))
            :<|> ((Named
                     '("iget", MlsE2EIdConfig)
                     (Description ""
                      :> (Summary "Get config for mlsE2EId"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("mlsE2EId"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature MlsE2EIdConfig))))))))))
                   :<|> (Named
                           '("iput", MlsE2EIdConfig)
                           (Description ""
                            :> (Summary "Put config for mlsE2EId"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("mlsE2EId"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature MlsE2EIdConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                MlsE2EIdConfig)))))))))))))
                         :<|> Named
                                '("ipatch", MlsE2EIdConfig)
                                (Description ""
                                 :> (Summary "Patch config for mlsE2EId"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("mlsE2EId"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  MlsE2EIdConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     MlsE2EIdConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", MlsMigrationConfig)
                           (Description ""
                            :> (Summary "Get config for mlsMigration"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("mlsMigration"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    MlsMigrationConfig))))))))))
                         :<|> (Named
                                 '("iput", MlsMigrationConfig)
                                 (Description ""
                                  :> (Summary "Put config for mlsMigration"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("mlsMigration"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   MlsMigrationConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      MlsMigrationConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", MlsMigrationConfig)
                                      (Description ""
                                       :> (Summary "Patch config for mlsMigration"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("mlsMigration"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        MlsMigrationConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           MlsMigrationConfig)))))))))))))))
                        :<|> ((Named
                                 '("iget", EnforceFileDownloadLocationConfig)
                                 (Description
                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                  :> (Summary "Get config for enforceFileDownloadLocation"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("enforceFileDownloadLocation"
                                                                  :> Get
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          EnforceFileDownloadLocationConfig))))))))))
                               :<|> (Named
                                       '("iput", EnforceFileDownloadLocationConfig)
                                       (Description
                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                        :> (Summary "Put config for enforceFileDownloadLocation"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("enforceFileDownloadLocation"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (Feature
                                                                                         EnforceFileDownloadLocationConfig)
                                                                                    :> Put
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            EnforceFileDownloadLocationConfig)))))))))))))
                                     :<|> Named
                                            '("ipatch", EnforceFileDownloadLocationConfig)
                                            (Description
                                               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                             :> (Summary
                                                   "Patch config for enforceFileDownloadLocation"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("enforceFileDownloadLocation"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (LockableFeaturePatch
                                                                                              EnforceFileDownloadLocationConfig)
                                                                                         :> Patch
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 EnforceFileDownloadLocationConfig)))))))))))))))
                              :<|> (Named
                                      '("iget", LimitedEventFanoutConfig)
                                      (Description ""
                                       :> (Summary "Get config for limitedEventFanout"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("limitedEventFanout"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               LimitedEventFanoutConfig))))))))))
                                    :<|> (Named
                                            '("iput", LimitedEventFanoutConfig)
                                            (Description ""
                                             :> (Summary "Put config for limitedEventFanout"
                                                 :> (CanThrow ('MissingPermission 'Nothing)
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow TeamFeatureError
                                                                 :> (CanThrowMany '[]
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("limitedEventFanout"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           (Feature
                                                                                              LimitedEventFanoutConfig)
                                                                                         :> Put
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 LimitedEventFanoutConfig)))))))))))))
                                          :<|> Named
                                                 '("ipatch", LimitedEventFanoutConfig)
                                                 (Description ""
                                                  :> (Summary "Patch config for limitedEventFanout"
                                                      :> (CanThrow ('MissingPermission 'Nothing)
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> (CanThrow TeamFeatureError
                                                                      :> (CanThrowMany '[]
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("limitedEventFanout"
                                                                                          :> (ReqBody
                                                                                                '[JSON]
                                                                                                (LockableFeaturePatch
                                                                                                   LimitedEventFanoutConfig)
                                                                                              :> Patch
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      LimitedEventFanoutConfig))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", OutlookCalIntegrationConfig)
     (Description ""
      :> (Summary "Get config for outlookCalIntegration"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("outlookCalIntegration"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature OutlookCalIntegrationConfig))))))))))
   :<|> (Named
           '("iput", OutlookCalIntegrationConfig)
           (Description ""
            :> (Summary "Put config for outlookCalIntegration"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("outlookCalIntegration"
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature OutlookCalIntegrationConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                OutlookCalIntegrationConfig)))))))))))))
         :<|> Named
                '("ipatch", OutlookCalIntegrationConfig)
                (Description ""
                 :> (Summary "Patch config for outlookCalIntegration"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("outlookCalIntegration"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  OutlookCalIntegrationConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     OutlookCalIntegrationConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", OutlookCalIntegrationConfig)
     (Description (FeatureAPIDesc OutlookCalIntegrationConfig)
      :> (Summary
            (AppendSymbol
               "Get config for " (FeatureSymbol OutlookCalIntegrationConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol OutlookCalIntegrationConfig
                                      :> Get
                                           '[JSON]
                                           (LockableFeature OutlookCalIntegrationConfig))))))))))
   :<|> (Named
           '("iput", OutlookCalIntegrationConfig)
           (Description (FeatureAPIDesc OutlookCalIntegrationConfig)
            :> (Summary
                  (AppendSymbol
                     "Put config for " (FeatureSymbol OutlookCalIntegrationConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors OutlookCalIntegrationConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol OutlookCalIntegrationConfig
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature OutlookCalIntegrationConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                OutlookCalIntegrationConfig)))))))))))))
         :<|> Named
                '("ipatch", OutlookCalIntegrationConfig)
                (Description (FeatureAPIDesc OutlookCalIntegrationConfig)
                 :> (Summary
                       (AppendSymbol
                          "Patch config for " (FeatureSymbol OutlookCalIntegrationConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany (FeatureErrors OutlookCalIntegrationConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol OutlookCalIntegrationConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  OutlookCalIntegrationConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     OutlookCalIntegrationConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", OutlookCalIntegrationConfig)
     (Description ""
      :> (Summary "Get config for outlookCalIntegration"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("outlookCalIntegration"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature OutlookCalIntegrationConfig))))))))))
   :<|> (Named
           '("iput", OutlookCalIntegrationConfig)
           (Description ""
            :> (Summary "Put config for outlookCalIntegration"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("outlookCalIntegration"
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature OutlookCalIntegrationConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                OutlookCalIntegrationConfig)))))))))))))
         :<|> Named
                '("ipatch", OutlookCalIntegrationConfig)
                (Description ""
                 :> (Summary "Patch config for outlookCalIntegration"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("outlookCalIntegration"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  OutlookCalIntegrationConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     OutlookCalIntegrationConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", MlsE2EIdConfig)
         (Description ""
          :> (Summary "Get config for mlsE2EId"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("mlsE2EId"
                                          :> Get '[JSON] (LockableFeature MlsE2EIdConfig))))))))))
       :<|> (Named
               '("iput", MlsE2EIdConfig)
               (Description ""
                :> (Summary "Put config for mlsE2EId"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("mlsE2EId"
                                                        :> (ReqBody '[JSON] (Feature MlsE2EIdConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    MlsE2EIdConfig)))))))))))))
             :<|> Named
                    '("ipatch", MlsE2EIdConfig)
                    (Description ""
                     :> (Summary "Patch config for mlsE2EId"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("mlsE2EId"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      MlsE2EIdConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         MlsE2EIdConfig)))))))))))))))
      :<|> ((Named
               '("iget", MlsMigrationConfig)
               (Description ""
                :> (Summary "Get config for mlsMigration"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("mlsMigration"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature MlsMigrationConfig))))))))))
             :<|> (Named
                     '("iput", MlsMigrationConfig)
                     (Description ""
                      :> (Summary "Put config for mlsMigration"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("mlsMigration"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature MlsMigrationConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          MlsMigrationConfig)))))))))))))
                   :<|> Named
                          '("ipatch", MlsMigrationConfig)
                          (Description ""
                           :> (Summary "Patch config for mlsMigration"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("mlsMigration"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            MlsMigrationConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               MlsMigrationConfig)))))))))))))))
            :<|> ((Named
                     '("iget", EnforceFileDownloadLocationConfig)
                     (Description
                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                      :> (Summary "Get config for enforceFileDownloadLocation"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("enforceFileDownloadLocation"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              EnforceFileDownloadLocationConfig))))))))))
                   :<|> (Named
                           '("iput", EnforceFileDownloadLocationConfig)
                           (Description
                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                            :> (Summary "Put config for enforceFileDownloadLocation"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("enforceFileDownloadLocation"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             EnforceFileDownloadLocationConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                EnforceFileDownloadLocationConfig)))))))))))))
                         :<|> Named
                                '("ipatch", EnforceFileDownloadLocationConfig)
                                (Description
                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                 :> (Summary "Patch config for enforceFileDownloadLocation"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("enforceFileDownloadLocation"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  EnforceFileDownloadLocationConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     EnforceFileDownloadLocationConfig)))))))))))))))
                  :<|> (Named
                          '("iget", LimitedEventFanoutConfig)
                          (Description ""
                           :> (Summary "Get config for limitedEventFanout"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("limitedEventFanout"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   LimitedEventFanoutConfig))))))))))
                        :<|> (Named
                                '("iput", LimitedEventFanoutConfig)
                                (Description ""
                                 :> (Summary "Put config for limitedEventFanout"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("limitedEventFanout"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (Feature
                                                                                  LimitedEventFanoutConfig)
                                                                             :> Put
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     LimitedEventFanoutConfig)))))))))))))
                              :<|> Named
                                     '("ipatch", LimitedEventFanoutConfig)
                                     (Description ""
                                      :> (Summary "Patch config for limitedEventFanout"
                                          :> (CanThrow ('MissingPermission 'Nothing)
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> (CanThrow TeamFeatureError
                                                          :> (CanThrowMany '[]
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("limitedEventFanout"
                                                                              :> (ReqBody
                                                                                    '[JSON]
                                                                                    (LockableFeaturePatch
                                                                                       LimitedEventFanoutConfig)
                                                                                  :> Patch
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          LimitedEventFanoutConfig))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", OutlookCalIntegrationConfig)
         (Description ""
          :> (Summary "Get config for outlookCalIntegration"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("outlookCalIntegration"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  OutlookCalIntegrationConfig))))))))))
       :<|> (Named
               '("iput", OutlookCalIntegrationConfig)
               (Description ""
                :> (Summary "Put config for outlookCalIntegration"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("outlookCalIntegration"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature OutlookCalIntegrationConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    OutlookCalIntegrationConfig)))))))))))))
             :<|> Named
                    '("ipatch", OutlookCalIntegrationConfig)
                    (Description ""
                     :> (Summary "Patch config for outlookCalIntegration"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("outlookCalIntegration"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      OutlookCalIntegrationConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         OutlookCalIntegrationConfig)))))))))))))))
      :<|> ((Named
               '("iget", MlsE2EIdConfig)
               (Description ""
                :> (Summary "Get config for mlsE2EId"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("mlsE2EId"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature MlsE2EIdConfig))))))))))
             :<|> (Named
                     '("iput", MlsE2EIdConfig)
                     (Description ""
                      :> (Summary "Put config for mlsE2EId"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("mlsE2EId"
                                                              :> (ReqBody
                                                                    '[JSON] (Feature MlsE2EIdConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          MlsE2EIdConfig)))))))))))))
                   :<|> Named
                          '("ipatch", MlsE2EIdConfig)
                          (Description ""
                           :> (Summary "Patch config for mlsE2EId"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("mlsE2EId"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            MlsE2EIdConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               MlsE2EIdConfig)))))))))))))))
            :<|> ((Named
                     '("iget", MlsMigrationConfig)
                     (Description ""
                      :> (Summary "Get config for mlsMigration"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("mlsMigration"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              MlsMigrationConfig))))))))))
                   :<|> (Named
                           '("iput", MlsMigrationConfig)
                           (Description ""
                            :> (Summary "Put config for mlsMigration"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("mlsMigration"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             MlsMigrationConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                MlsMigrationConfig)))))))))))))
                         :<|> Named
                                '("ipatch", MlsMigrationConfig)
                                (Description ""
                                 :> (Summary "Patch config for mlsMigration"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("mlsMigration"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  MlsMigrationConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     MlsMigrationConfig)))))))))))))))
                  :<|> ((Named
                           '("iget", EnforceFileDownloadLocationConfig)
                           (Description
                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                            :> (Summary "Get config for enforceFileDownloadLocation"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("enforceFileDownloadLocation"
                                                            :> Get
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    EnforceFileDownloadLocationConfig))))))))))
                         :<|> (Named
                                 '("iput", EnforceFileDownloadLocationConfig)
                                 (Description
                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                  :> (Summary "Put config for enforceFileDownloadLocation"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("enforceFileDownloadLocation"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (Feature
                                                                                   EnforceFileDownloadLocationConfig)
                                                                              :> Put
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      EnforceFileDownloadLocationConfig)))))))))))))
                               :<|> Named
                                      '("ipatch", EnforceFileDownloadLocationConfig)
                                      (Description
                                         "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                       :> (Summary "Patch config for enforceFileDownloadLocation"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("enforceFileDownloadLocation"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (LockableFeaturePatch
                                                                                        EnforceFileDownloadLocationConfig)
                                                                                   :> Patch
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           EnforceFileDownloadLocationConfig)))))))))))))))
                        :<|> (Named
                                '("iget", LimitedEventFanoutConfig)
                                (Description ""
                                 :> (Summary "Get config for limitedEventFanout"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("limitedEventFanout"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         LimitedEventFanoutConfig))))))))))
                              :<|> (Named
                                      '("iput", LimitedEventFanoutConfig)
                                      (Description ""
                                       :> (Summary "Put config for limitedEventFanout"
                                           :> (CanThrow ('MissingPermission 'Nothing)
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow TeamFeatureError
                                                           :> (CanThrowMany '[]
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("limitedEventFanout"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     (Feature
                                                                                        LimitedEventFanoutConfig)
                                                                                   :> Put
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           LimitedEventFanoutConfig)))))))))))))
                                    :<|> Named
                                           '("ipatch", LimitedEventFanoutConfig)
                                           (Description ""
                                            :> (Summary "Patch config for limitedEventFanout"
                                                :> (CanThrow ('MissingPermission 'Nothing)
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> (CanThrow TeamFeatureError
                                                                :> (CanThrowMany '[]
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("limitedEventFanout"
                                                                                    :> (ReqBody
                                                                                          '[JSON]
                                                                                          (LockableFeaturePatch
                                                                                             LimitedEventFanoutConfig)
                                                                                        :> Patch
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                LimitedEventFanoutConfig)))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", MlsE2EIdConfig)
     (Description ""
      :> (Summary "Get config for mlsE2EId"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("mlsE2EId"
                                      :> Get '[JSON] (LockableFeature MlsE2EIdConfig))))))))))
   :<|> (Named
           '("iput", MlsE2EIdConfig)
           (Description ""
            :> (Summary "Put config for mlsE2EId"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("mlsE2EId"
                                                    :> (ReqBody '[JSON] (Feature MlsE2EIdConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                MlsE2EIdConfig)))))))))))))
         :<|> Named
                '("ipatch", MlsE2EIdConfig)
                (Description ""
                 :> (Summary "Patch config for mlsE2EId"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("mlsE2EId"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch MlsE2EIdConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     MlsE2EIdConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", MlsE2EIdConfig)
     (Description (FeatureAPIDesc MlsE2EIdConfig)
      :> (Summary
            (AppendSymbol "Get config for " (FeatureSymbol MlsE2EIdConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol MlsE2EIdConfig
                                      :> Get '[JSON] (LockableFeature MlsE2EIdConfig))))))))))
   :<|> (Named
           '("iput", MlsE2EIdConfig)
           (Description (FeatureAPIDesc MlsE2EIdConfig)
            :> (Summary
                  (AppendSymbol "Put config for " (FeatureSymbol MlsE2EIdConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors MlsE2EIdConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol MlsE2EIdConfig
                                                    :> (ReqBody '[JSON] (Feature MlsE2EIdConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                MlsE2EIdConfig)))))))))))))
         :<|> Named
                '("ipatch", MlsE2EIdConfig)
                (Description (FeatureAPIDesc MlsE2EIdConfig)
                 :> (Summary
                       (AppendSymbol "Patch config for " (FeatureSymbol MlsE2EIdConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany (FeatureErrors MlsE2EIdConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol MlsE2EIdConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch MlsE2EIdConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     MlsE2EIdConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", MlsE2EIdConfig)
     (Description ""
      :> (Summary "Get config for mlsE2EId"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("mlsE2EId"
                                      :> Get '[JSON] (LockableFeature MlsE2EIdConfig))))))))))
   :<|> (Named
           '("iput", MlsE2EIdConfig)
           (Description ""
            :> (Summary "Put config for mlsE2EId"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("mlsE2EId"
                                                    :> (ReqBody '[JSON] (Feature MlsE2EIdConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                MlsE2EIdConfig)))))))))))))
         :<|> Named
                '("ipatch", MlsE2EIdConfig)
                (Description ""
                 :> (Summary "Patch config for mlsE2EId"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("mlsE2EId"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch MlsE2EIdConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     MlsE2EIdConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", MlsMigrationConfig)
         (Description ""
          :> (Summary "Get config for mlsMigration"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("mlsMigration"
                                          :> Get
                                               '[JSON] (LockableFeature MlsMigrationConfig))))))))))
       :<|> (Named
               '("iput", MlsMigrationConfig)
               (Description ""
                :> (Summary "Put config for mlsMigration"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("mlsMigration"
                                                        :> (ReqBody
                                                              '[JSON] (Feature MlsMigrationConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    MlsMigrationConfig)))))))))))))
             :<|> Named
                    '("ipatch", MlsMigrationConfig)
                    (Description ""
                     :> (Summary "Patch config for mlsMigration"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("mlsMigration"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      MlsMigrationConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         MlsMigrationConfig)))))))))))))))
      :<|> ((Named
               '("iget", EnforceFileDownloadLocationConfig)
               (Description
                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                :> (Summary "Get config for enforceFileDownloadLocation"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("enforceFileDownloadLocation"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        EnforceFileDownloadLocationConfig))))))))))
             :<|> (Named
                     '("iput", EnforceFileDownloadLocationConfig)
                     (Description
                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                      :> (Summary "Put config for enforceFileDownloadLocation"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("enforceFileDownloadLocation"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       EnforceFileDownloadLocationConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          EnforceFileDownloadLocationConfig)))))))))))))
                   :<|> Named
                          '("ipatch", EnforceFileDownloadLocationConfig)
                          (Description
                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                           :> (Summary "Patch config for enforceFileDownloadLocation"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("enforceFileDownloadLocation"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            EnforceFileDownloadLocationConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               EnforceFileDownloadLocationConfig)))))))))))))))
            :<|> (Named
                    '("iget", LimitedEventFanoutConfig)
                    (Description ""
                     :> (Summary "Get config for limitedEventFanout"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> ("teams"
                                         :> (Capture "tid" TeamId
                                             :> ("features"
                                                 :> ("limitedEventFanout"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             LimitedEventFanoutConfig))))))))))
                  :<|> (Named
                          '("iput", LimitedEventFanoutConfig)
                          (Description ""
                           :> (Summary "Put config for limitedEventFanout"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("limitedEventFanout"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (Feature
                                                                            LimitedEventFanoutConfig)
                                                                       :> Put
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               LimitedEventFanoutConfig)))))))))))))
                        :<|> Named
                               '("ipatch", LimitedEventFanoutConfig)
                               (Description ""
                                :> (Summary "Patch config for limitedEventFanout"
                                    :> (CanThrow ('MissingPermission 'Nothing)
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> (CanThrow TeamFeatureError
                                                    :> (CanThrowMany '[]
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("limitedEventFanout"
                                                                        :> (ReqBody
                                                                              '[JSON]
                                                                              (LockableFeaturePatch
                                                                                 LimitedEventFanoutConfig)
                                                                            :> Patch
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    LimitedEventFanoutConfig)))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", MlsE2EIdConfig)
         (Description ""
          :> (Summary "Get config for mlsE2EId"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("mlsE2EId"
                                          :> Get '[JSON] (LockableFeature MlsE2EIdConfig))))))))))
       :<|> (Named
               '("iput", MlsE2EIdConfig)
               (Description ""
                :> (Summary "Put config for mlsE2EId"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("mlsE2EId"
                                                        :> (ReqBody '[JSON] (Feature MlsE2EIdConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    MlsE2EIdConfig)))))))))))))
             :<|> Named
                    '("ipatch", MlsE2EIdConfig)
                    (Description ""
                     :> (Summary "Patch config for mlsE2EId"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("mlsE2EId"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      MlsE2EIdConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         MlsE2EIdConfig)))))))))))))))
      :<|> ((Named
               '("iget", MlsMigrationConfig)
               (Description ""
                :> (Summary "Get config for mlsMigration"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("mlsMigration"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature MlsMigrationConfig))))))))))
             :<|> (Named
                     '("iput", MlsMigrationConfig)
                     (Description ""
                      :> (Summary "Put config for mlsMigration"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("mlsMigration"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature MlsMigrationConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          MlsMigrationConfig)))))))))))))
                   :<|> Named
                          '("ipatch", MlsMigrationConfig)
                          (Description ""
                           :> (Summary "Patch config for mlsMigration"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("mlsMigration"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            MlsMigrationConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               MlsMigrationConfig)))))))))))))))
            :<|> ((Named
                     '("iget", EnforceFileDownloadLocationConfig)
                     (Description
                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                      :> (Summary "Get config for enforceFileDownloadLocation"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("enforceFileDownloadLocation"
                                                      :> Get
                                                           '[JSON]
                                                           (LockableFeature
                                                              EnforceFileDownloadLocationConfig))))))))))
                   :<|> (Named
                           '("iput", EnforceFileDownloadLocationConfig)
                           (Description
                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                            :> (Summary "Put config for enforceFileDownloadLocation"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("enforceFileDownloadLocation"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (Feature
                                                                             EnforceFileDownloadLocationConfig)
                                                                        :> Put
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                EnforceFileDownloadLocationConfig)))))))))))))
                         :<|> Named
                                '("ipatch", EnforceFileDownloadLocationConfig)
                                (Description
                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                 :> (Summary "Patch config for enforceFileDownloadLocation"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("enforceFileDownloadLocation"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (LockableFeaturePatch
                                                                                  EnforceFileDownloadLocationConfig)
                                                                             :> Patch
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     EnforceFileDownloadLocationConfig)))))))))))))))
                  :<|> (Named
                          '("iget", LimitedEventFanoutConfig)
                          (Description ""
                           :> (Summary "Get config for limitedEventFanout"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("limitedEventFanout"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   LimitedEventFanoutConfig))))))))))
                        :<|> (Named
                                '("iput", LimitedEventFanoutConfig)
                                (Description ""
                                 :> (Summary "Put config for limitedEventFanout"
                                     :> (CanThrow ('MissingPermission 'Nothing)
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (CanThrowMany '[]
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("limitedEventFanout"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               (Feature
                                                                                  LimitedEventFanoutConfig)
                                                                             :> Put
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     LimitedEventFanoutConfig)))))))))))))
                              :<|> Named
                                     '("ipatch", LimitedEventFanoutConfig)
                                     (Description ""
                                      :> (Summary "Patch config for limitedEventFanout"
                                          :> (CanThrow ('MissingPermission 'Nothing)
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> (CanThrow TeamFeatureError
                                                          :> (CanThrowMany '[]
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("limitedEventFanout"
                                                                              :> (ReqBody
                                                                                    '[JSON]
                                                                                    (LockableFeaturePatch
                                                                                       LimitedEventFanoutConfig)
                                                                                  :> Patch
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          LimitedEventFanoutConfig))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", MlsMigrationConfig)
     (Description ""
      :> (Summary "Get config for mlsMigration"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("mlsMigration"
                                      :> Get '[JSON] (LockableFeature MlsMigrationConfig))))))))))
   :<|> (Named
           '("iput", MlsMigrationConfig)
           (Description ""
            :> (Summary "Put config for mlsMigration"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("mlsMigration"
                                                    :> (ReqBody '[JSON] (Feature MlsMigrationConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                MlsMigrationConfig)))))))))))))
         :<|> Named
                '("ipatch", MlsMigrationConfig)
                (Description ""
                 :> (Summary "Patch config for mlsMigration"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("mlsMigration"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  MlsMigrationConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     MlsMigrationConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", MlsMigrationConfig)
     (Description (FeatureAPIDesc MlsMigrationConfig)
      :> (Summary
            (AppendSymbol "Get config for " (FeatureSymbol MlsMigrationConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol MlsMigrationConfig
                                      :> Get '[JSON] (LockableFeature MlsMigrationConfig))))))))))
   :<|> (Named
           '("iput", MlsMigrationConfig)
           (Description (FeatureAPIDesc MlsMigrationConfig)
            :> (Summary
                  (AppendSymbol "Put config for " (FeatureSymbol MlsMigrationConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors MlsMigrationConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol MlsMigrationConfig
                                                    :> (ReqBody '[JSON] (Feature MlsMigrationConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                MlsMigrationConfig)))))))))))))
         :<|> Named
                '("ipatch", MlsMigrationConfig)
                (Description (FeatureAPIDesc MlsMigrationConfig)
                 :> (Summary
                       (AppendSymbol
                          "Patch config for " (FeatureSymbol MlsMigrationConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany (FeatureErrors MlsMigrationConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol MlsMigrationConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  MlsMigrationConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     MlsMigrationConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", MlsMigrationConfig)
     (Description ""
      :> (Summary "Get config for mlsMigration"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("mlsMigration"
                                      :> Get '[JSON] (LockableFeature MlsMigrationConfig))))))))))
   :<|> (Named
           '("iput", MlsMigrationConfig)
           (Description ""
            :> (Summary "Put config for mlsMigration"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("mlsMigration"
                                                    :> (ReqBody '[JSON] (Feature MlsMigrationConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                MlsMigrationConfig)))))))))))))
         :<|> Named
                '("ipatch", MlsMigrationConfig)
                (Description ""
                 :> (Summary "Patch config for mlsMigration"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("mlsMigration"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  MlsMigrationConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     MlsMigrationConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
         '("iget", EnforceFileDownloadLocationConfig)
         (Description
            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
          :> (Summary "Get config for enforceFileDownloadLocation"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("enforceFileDownloadLocation"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  EnforceFileDownloadLocationConfig))))))))))
       :<|> (Named
               '("iput", EnforceFileDownloadLocationConfig)
               (Description
                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                :> (Summary "Put config for enforceFileDownloadLocation"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("enforceFileDownloadLocation"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature
                                                                 EnforceFileDownloadLocationConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    EnforceFileDownloadLocationConfig)))))))))))))
             :<|> Named
                    '("ipatch", EnforceFileDownloadLocationConfig)
                    (Description
                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                     :> (Summary "Patch config for enforceFileDownloadLocation"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("enforceFileDownloadLocation"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      EnforceFileDownloadLocationConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         EnforceFileDownloadLocationConfig)))))))))))))))
      :<|> (Named
              '("iget", LimitedEventFanoutConfig)
              (Description ""
               :> (Summary "Get config for limitedEventFanout"
                   :> (CanThrow ('MissingPermission 'Nothing)
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> ("teams"
                                   :> (Capture "tid" TeamId
                                       :> ("features"
                                           :> ("limitedEventFanout"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       LimitedEventFanoutConfig))))))))))
            :<|> (Named
                    '("iput", LimitedEventFanoutConfig)
                    (Description ""
                     :> (Summary "Put config for limitedEventFanout"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("limitedEventFanout"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (Feature
                                                                      LimitedEventFanoutConfig)
                                                                 :> Put
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         LimitedEventFanoutConfig)))))))))))))
                  :<|> Named
                         '("ipatch", LimitedEventFanoutConfig)
                         (Description ""
                          :> (Summary "Patch config for limitedEventFanout"
                              :> (CanThrow ('MissingPermission 'Nothing)
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> (CanThrow TeamFeatureError
                                              :> (CanThrowMany '[]
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("limitedEventFanout"
                                                                  :> (ReqBody
                                                                        '[JSON]
                                                                        (LockableFeaturePatch
                                                                           LimitedEventFanoutConfig)
                                                                      :> Patch
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              LimitedEventFanoutConfig))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", MlsMigrationConfig)
         (Description ""
          :> (Summary "Get config for mlsMigration"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("mlsMigration"
                                          :> Get
                                               '[JSON] (LockableFeature MlsMigrationConfig))))))))))
       :<|> (Named
               '("iput", MlsMigrationConfig)
               (Description ""
                :> (Summary "Put config for mlsMigration"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("mlsMigration"
                                                        :> (ReqBody
                                                              '[JSON] (Feature MlsMigrationConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    MlsMigrationConfig)))))))))))))
             :<|> Named
                    '("ipatch", MlsMigrationConfig)
                    (Description ""
                     :> (Summary "Patch config for mlsMigration"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("mlsMigration"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      MlsMigrationConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         MlsMigrationConfig)))))))))))))))
      :<|> ((Named
               '("iget", EnforceFileDownloadLocationConfig)
               (Description
                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                :> (Summary "Get config for enforceFileDownloadLocation"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("enforceFileDownloadLocation"
                                                :> Get
                                                     '[JSON]
                                                     (LockableFeature
                                                        EnforceFileDownloadLocationConfig))))))))))
             :<|> (Named
                     '("iput", EnforceFileDownloadLocationConfig)
                     (Description
                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                      :> (Summary "Put config for enforceFileDownloadLocation"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("enforceFileDownloadLocation"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       EnforceFileDownloadLocationConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          EnforceFileDownloadLocationConfig)))))))))))))
                   :<|> Named
                          '("ipatch", EnforceFileDownloadLocationConfig)
                          (Description
                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                           :> (Summary "Patch config for enforceFileDownloadLocation"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("enforceFileDownloadLocation"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (LockableFeaturePatch
                                                                            EnforceFileDownloadLocationConfig)
                                                                       :> Patch
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               EnforceFileDownloadLocationConfig)))))))))))))))
            :<|> (Named
                    '("iget", LimitedEventFanoutConfig)
                    (Description ""
                     :> (Summary "Get config for limitedEventFanout"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> ("teams"
                                         :> (Capture "tid" TeamId
                                             :> ("features"
                                                 :> ("limitedEventFanout"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             LimitedEventFanoutConfig))))))))))
                  :<|> (Named
                          '("iput", LimitedEventFanoutConfig)
                          (Description ""
                           :> (Summary "Put config for limitedEventFanout"
                               :> (CanThrow ('MissingPermission 'Nothing)
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (CanThrowMany '[]
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("limitedEventFanout"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         (Feature
                                                                            LimitedEventFanoutConfig)
                                                                       :> Put
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               LimitedEventFanoutConfig)))))))))))))
                        :<|> Named
                               '("ipatch", LimitedEventFanoutConfig)
                               (Description ""
                                :> (Summary "Patch config for limitedEventFanout"
                                    :> (CanThrow ('MissingPermission 'Nothing)
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> (CanThrow TeamFeatureError
                                                    :> (CanThrowMany '[]
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("limitedEventFanout"
                                                                        :> (ReqBody
                                                                              '[JSON]
                                                                              (LockableFeaturePatch
                                                                                 LimitedEventFanoutConfig)
                                                                            :> Patch
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    LimitedEventFanoutConfig)))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", EnforceFileDownloadLocationConfig)
     (Description
        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
      :> (Summary "Get config for enforceFileDownloadLocation"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("enforceFileDownloadLocation"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature
                                              EnforceFileDownloadLocationConfig))))))))))
   :<|> (Named
           '("iput", EnforceFileDownloadLocationConfig)
           (Description
              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
            :> (Summary "Put config for enforceFileDownloadLocation"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("enforceFileDownloadLocation"
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature
                                                             EnforceFileDownloadLocationConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                EnforceFileDownloadLocationConfig)))))))))))))
         :<|> Named
                '("ipatch", EnforceFileDownloadLocationConfig)
                (Description
                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                 :> (Summary "Patch config for enforceFileDownloadLocation"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("enforceFileDownloadLocation"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  EnforceFileDownloadLocationConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     EnforceFileDownloadLocationConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", EnforceFileDownloadLocationConfig)
     (Description (FeatureAPIDesc EnforceFileDownloadLocationConfig)
      :> (Summary
            (AppendSymbol
               "Get config for "
               (FeatureSymbol EnforceFileDownloadLocationConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol EnforceFileDownloadLocationConfig
                                      :> Get
                                           '[JSON]
                                           (LockableFeature
                                              EnforceFileDownloadLocationConfig))))))))))
   :<|> (Named
           '("iput", EnforceFileDownloadLocationConfig)
           (Description (FeatureAPIDesc EnforceFileDownloadLocationConfig)
            :> (Summary
                  (AppendSymbol
                     "Put config for "
                     (FeatureSymbol EnforceFileDownloadLocationConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors EnforceFileDownloadLocationConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol EnforceFileDownloadLocationConfig
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature
                                                             EnforceFileDownloadLocationConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                EnforceFileDownloadLocationConfig)))))))))))))
         :<|> Named
                '("ipatch", EnforceFileDownloadLocationConfig)
                (Description (FeatureAPIDesc EnforceFileDownloadLocationConfig)
                 :> (Summary
                       (AppendSymbol
                          "Patch config for "
                          (FeatureSymbol EnforceFileDownloadLocationConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany
                                           (FeatureErrors EnforceFileDownloadLocationConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol
                                                           EnforceFileDownloadLocationConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  EnforceFileDownloadLocationConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     EnforceFileDownloadLocationConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full
    API
  (Named
     '("iget", EnforceFileDownloadLocationConfig)
     (Description
        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
      :> (Summary "Get config for enforceFileDownloadLocation"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("enforceFileDownloadLocation"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature
                                              EnforceFileDownloadLocationConfig))))))))))
   :<|> (Named
           '("iput", EnforceFileDownloadLocationConfig)
           (Description
              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
            :> (Summary "Put config for enforceFileDownloadLocation"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("enforceFileDownloadLocation"
                                                    :> (ReqBody
                                                          '[JSON]
                                                          (Feature
                                                             EnforceFileDownloadLocationConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                EnforceFileDownloadLocationConfig)))))))))))))
         :<|> Named
                '("ipatch", EnforceFileDownloadLocationConfig)
                (Description
                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                 :> (Summary "Patch config for enforceFileDownloadLocation"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("enforceFileDownloadLocation"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  EnforceFileDownloadLocationConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     EnforceFileDownloadLocationConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        '("iget", LimitedEventFanoutConfig)
        (Description ""
         :> (Summary "Get config for limitedEventFanout"
             :> (CanThrow ('MissingPermission 'Nothing)
                 :> (CanThrow 'NotATeamMember
                     :> (CanThrow 'TeamNotFound
                         :> ("teams"
                             :> (Capture "tid" TeamId
                                 :> ("features"
                                     :> ("limitedEventFanout"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature LimitedEventFanoutConfig))))))))))
      :<|> (Named
              '("iput", LimitedEventFanoutConfig)
              (Description ""
               :> (Summary "Put config for limitedEventFanout"
                   :> (CanThrow ('MissingPermission 'Nothing)
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("limitedEventFanout"
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature LimitedEventFanoutConfig)
                                                           :> Put
                                                                '[JSON]
                                                                (LockableFeature
                                                                   LimitedEventFanoutConfig)))))))))))))
            :<|> Named
                   '("ipatch", LimitedEventFanoutConfig)
                   (Description ""
                    :> (Summary "Patch config for limitedEventFanout"
                        :> (CanThrow ('MissingPermission 'Nothing)
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> (CanThrow TeamFeatureError
                                        :> (CanThrowMany '[]
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("limitedEventFanout"
                                                            :> (ReqBody
                                                                  '[JSON]
                                                                  (LockableFeaturePatch
                                                                     LimitedEventFanoutConfig)
                                                                :> Patch
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        LimitedEventFanoutConfig)))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
         '("iget", EnforceFileDownloadLocationConfig)
         (Description
            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
          :> (Summary "Get config for enforceFileDownloadLocation"
              :> (CanThrow ('MissingPermission 'Nothing)
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("enforceFileDownloadLocation"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  EnforceFileDownloadLocationConfig))))))))))
       :<|> (Named
               '("iput", EnforceFileDownloadLocationConfig)
               (Description
                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                :> (Summary "Put config for enforceFileDownloadLocation"
                    :> (CanThrow ('MissingPermission 'Nothing)
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany '[]
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("enforceFileDownloadLocation"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature
                                                                 EnforceFileDownloadLocationConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    EnforceFileDownloadLocationConfig)))))))))))))
             :<|> Named
                    '("ipatch", EnforceFileDownloadLocationConfig)
                    (Description
                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                     :> (Summary "Patch config for enforceFileDownloadLocation"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("enforceFileDownloadLocation"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (LockableFeaturePatch
                                                                      EnforceFileDownloadLocationConfig)
                                                                 :> Patch
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         EnforceFileDownloadLocationConfig)))))))))))))))
      :<|> (Named
              '("iget", LimitedEventFanoutConfig)
              (Description ""
               :> (Summary "Get config for limitedEventFanout"
                   :> (CanThrow ('MissingPermission 'Nothing)
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> ("teams"
                                   :> (Capture "tid" TeamId
                                       :> ("features"
                                           :> ("limitedEventFanout"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       LimitedEventFanoutConfig))))))))))
            :<|> (Named
                    '("iput", LimitedEventFanoutConfig)
                    (Description ""
                     :> (Summary "Put config for limitedEventFanout"
                         :> (CanThrow ('MissingPermission 'Nothing)
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (CanThrowMany '[]
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("limitedEventFanout"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   (Feature
                                                                      LimitedEventFanoutConfig)
                                                                 :> Put
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         LimitedEventFanoutConfig)))))))))))))
                  :<|> Named
                         '("ipatch", LimitedEventFanoutConfig)
                         (Description ""
                          :> (Summary "Patch config for limitedEventFanout"
                              :> (CanThrow ('MissingPermission 'Nothing)
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> (CanThrow TeamFeatureError
                                              :> (CanThrowMany '[]
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("limitedEventFanout"
                                                                  :> (ReqBody
                                                                        '[JSON]
                                                                        (LockableFeaturePatch
                                                                           LimitedEventFanoutConfig)
                                                                      :> Patch
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              LimitedEventFanoutConfig))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
<@> API
  (Named
     '("iget", LimitedEventFanoutConfig)
     (Description ""
      :> (Summary "Get config for limitedEventFanout"
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> ("limitedEventFanout"
                                      :> Get
                                           '[JSON]
                                           (LockableFeature LimitedEventFanoutConfig))))))))))
   :<|> (Named
           '("iput", LimitedEventFanoutConfig)
           (Description ""
            :> (Summary "Put config for limitedEventFanout"
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany '[]
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("limitedEventFanout"
                                                    :> (ReqBody
                                                          '[JSON] (Feature LimitedEventFanoutConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                LimitedEventFanoutConfig)))))))))))))
         :<|> Named
                '("ipatch", LimitedEventFanoutConfig)
                (Description ""
                 :> (Summary "Patch config for limitedEventFanout"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("limitedEventFanout"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  LimitedEventFanoutConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     LimitedEventFanoutConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
     '("iget", LimitedEventFanoutConfig)
     (Description (FeatureAPIDesc LimitedEventFanoutConfig)
      :> (Summary
            (AppendSymbol
               "Get config for " (FeatureSymbol LimitedEventFanoutConfig))
          :> (CanThrow ('MissingPermission 'Nothing)
              :> (CanThrow 'NotATeamMember
                  :> (CanThrow 'TeamNotFound
                      :> ("teams"
                          :> (Capture "tid" TeamId
                              :> ("features"
                                  :> (FeatureSymbol LimitedEventFanoutConfig
                                      :> Get
                                           '[JSON]
                                           (LockableFeature LimitedEventFanoutConfig))))))))))
   :<|> (Named
           '("iput", LimitedEventFanoutConfig)
           (Description (FeatureAPIDesc LimitedEventFanoutConfig)
            :> (Summary
                  (AppendSymbol
                     "Put config for " (FeatureSymbol LimitedEventFanoutConfig))
                :> (CanThrow ('MissingPermission 'Nothing)
                    :> (CanThrow 'NotATeamMember
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow TeamFeatureError
                                :> (CanThrowMany (FeatureErrors LimitedEventFanoutConfig)
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> (FeatureSymbol LimitedEventFanoutConfig
                                                    :> (ReqBody
                                                          '[JSON] (Feature LimitedEventFanoutConfig)
                                                        :> Put
                                                             '[JSON]
                                                             (LockableFeature
                                                                LimitedEventFanoutConfig)))))))))))))
         :<|> Named
                '("ipatch", LimitedEventFanoutConfig)
                (Description (FeatureAPIDesc LimitedEventFanoutConfig)
                 :> (Summary
                       (AppendSymbol
                          "Patch config for " (FeatureSymbol LimitedEventFanoutConfig))
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany (FeatureErrors LimitedEventFanoutConfig)
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> (FeatureSymbol LimitedEventFanoutConfig
                                                         :> (ReqBody
                                                               '[JSON]
                                                               (LockableFeaturePatch
                                                                  LimitedEventFanoutConfig)
                                                             :> Patch
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     LimitedEventFanoutConfig)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 cfg (r :: EffectRow).
(ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (Feature cfg)
                                  :> Put '[JSON] (LockableFeature cfg))))))))
          r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureForTeamConstraints
   cfg
   (Error (Tagged ('MissingPermission 'Nothing) ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : Error TeamFeatureError
      : Append
          (DeclaredErrorEffects
             (CanThrowMany (FeatureErrors cfg)
              :> ("teams"
                  :> (Capture "tid" TeamId
                      :> ("features"
                          :> (FeatureSymbol cfg
                              :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                                  :> Patch '[JSON] (LockableFeature cfg))))))))
          r),
 SetFeatureConfig cfg,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                           :> Patch '[JSON] (LockableFeature cfg))))))))
   r,
 Member (Input Opts) r,
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Input Opts)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member (Error DynError) r,
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Error DynError)
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   (Logger (Msg -> Msg))
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamStore r,
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member TeamFeatureStore r,
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   TeamFeatureStore
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r),
 Member
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (LockableFeaturePatch cfg)
                              :> Patch '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (IFeatureAPI1Full cfg) r
featureAPI1Full

featureAPI :: API IFeatureAPI GalleyEffects
featureAPI :: API IFeatureAPI GalleyEffects
featureAPI =
  API
  ((Named
      '("iget", LegalholdConfig)
      (Description ""
       :> (Summary "Get config for legalhold"
           :> (CanThrow ('MissingPermission 'Nothing)
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow 'TeamNotFound
                       :> ("teams"
                           :> (Capture "tid" TeamId
                               :> ("features"
                                   :> ("legalhold"
                                       :> Get '[JSON] (LockableFeature LegalholdConfig))))))))))
    :<|> (Named
            '("iput", LegalholdConfig)
            (Description ""
             :> (Summary "Put config for legalhold"
                 :> (CanThrow ('MissingPermission 'Nothing)
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> (CanThrow TeamFeatureError
                                 :> (CanThrowMany
                                       '[ 'ActionDenied 'RemoveConversationMember,
                                          'CannotEnableLegalHoldServiceLargeTeam,
                                          'LegalHoldNotEnabled, 'LegalHoldDisableUnimplemented,
                                          'LegalHoldServiceNotRegistered,
                                          'UserLegalHoldIllegalOperation,
                                          'LegalHoldCouldNotBlockConnections]
                                     :> ("teams"
                                         :> (Capture "tid" TeamId
                                             :> ("features"
                                                 :> ("legalhold"
                                                     :> (ReqBody '[JSON] (Feature LegalholdConfig)
                                                         :> Put
                                                              '[JSON]
                                                              (LockableFeature
                                                                 LegalholdConfig)))))))))))))
          :<|> Named
                 '("ipatch", LegalholdConfig)
                 (Description ""
                  :> (Summary "Patch config for legalhold"
                      :> (CanThrow ('MissingPermission 'Nothing)
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> (CanThrow TeamFeatureError
                                      :> (CanThrowMany
                                            '[ 'ActionDenied 'RemoveConversationMember,
                                               'CannotEnableLegalHoldServiceLargeTeam,
                                               'LegalHoldNotEnabled, 'LegalHoldDisableUnimplemented,
                                               'LegalHoldServiceNotRegistered,
                                               'UserLegalHoldIllegalOperation,
                                               'LegalHoldCouldNotBlockConnections]
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("legalhold"
                                                          :> (ReqBody
                                                                '[JSON]
                                                                (LockableFeaturePatch
                                                                   LegalholdConfig)
                                                              :> Patch
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      LegalholdConfig)))))))))))))))
   :<|> ((Named
            '("iget", SSOConfig)
            (Description ""
             :> (Summary "Get config for sso"
                 :> (CanThrow ('MissingPermission 'Nothing)
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features"
                                         :> ("sso"
                                             :> Get '[JSON] (LockableFeature SSOConfig))))))))))
          :<|> (Named
                  '("iput", SSOConfig)
                  (Description ""
                   :> (Summary "Put config for sso"
                       :> (CanThrow ('MissingPermission 'Nothing)
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("sso"
                                                           :> (ReqBody '[JSON] (Feature SSOConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       SSOConfig)))))))))))))
                :<|> Named
                       '("ipatch", SSOConfig)
                       (Description ""
                        :> (Summary "Patch config for sso"
                            :> (CanThrow ('MissingPermission 'Nothing)
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> (CanThrow TeamFeatureError
                                            :> (CanThrowMany '[]
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("sso"
                                                                :> (ReqBody
                                                                      '[JSON]
                                                                      (LockableFeaturePatch
                                                                         SSOConfig)
                                                                    :> Patch
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            SSOConfig)))))))))))))))
         :<|> ((Named
                  '("iget", SearchVisibilityAvailableConfig)
                  (Description ""
                   :> (Summary "Get config for searchVisibility"
                       :> (CanThrow ('MissingPermission 'Nothing)
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> ("teams"
                                       :> (Capture "tid" TeamId
                                           :> ("features"
                                               :> ("searchVisibility"
                                                   :> Get
                                                        '[JSON]
                                                        (LockableFeature
                                                           SearchVisibilityAvailableConfig))))))))))
                :<|> (Named
                        '("iput", SearchVisibilityAvailableConfig)
                        (Description ""
                         :> (Summary "Put config for searchVisibility"
                             :> (CanThrow ('MissingPermission 'Nothing)
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("searchVisibility"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          SearchVisibilityAvailableConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             SearchVisibilityAvailableConfig)))))))))))))
                      :<|> Named
                             '("ipatch", SearchVisibilityAvailableConfig)
                             (Description ""
                              :> (Summary "Patch config for searchVisibility"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> (CanThrow TeamFeatureError
                                                  :> (CanThrowMany '[]
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("searchVisibility"
                                                                      :> (ReqBody
                                                                            '[JSON]
                                                                            (LockableFeaturePatch
                                                                               SearchVisibilityAvailableConfig)
                                                                          :> Patch
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  SearchVisibilityAvailableConfig)))))))))))))))
               :<|> ((Named
                        '("iget", SearchVisibilityInboundConfig)
                        (Description ""
                         :> (Summary "Get config for searchVisibilityInbound"
                             :> (CanThrow ('MissingPermission 'Nothing)
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("searchVisibilityInbound"
                                                         :> Get
                                                              '[JSON]
                                                              (LockableFeature
                                                                 SearchVisibilityInboundConfig))))))))))
                      :<|> (Named
                              '("iput", SearchVisibilityInboundConfig)
                              (Description ""
                               :> (Summary "Put config for searchVisibilityInbound"
                                   :> (CanThrow ('MissingPermission 'Nothing)
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("searchVisibilityInbound"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                SearchVisibilityInboundConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   SearchVisibilityInboundConfig)))))))))))))
                            :<|> Named
                                   '("ipatch", SearchVisibilityInboundConfig)
                                   (Description ""
                                    :> (Summary "Patch config for searchVisibilityInbound"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> (CanThrow TeamFeatureError
                                                        :> (CanThrowMany '[]
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("searchVisibilityInbound"
                                                                            :> (ReqBody
                                                                                  '[JSON]
                                                                                  (LockableFeaturePatch
                                                                                     SearchVisibilityInboundConfig)
                                                                                :> Patch
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SearchVisibilityInboundConfig)))))))))))))))
                     :<|> ((Named
                              '("iget", ValidateSAMLEmailsConfig)
                              (Description ""
                               :> (Summary "Get config for validateSAMLemails"
                                   :> (CanThrow ('MissingPermission 'Nothing)
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("validateSAMLemails"
                                                               :> Get
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       ValidateSAMLEmailsConfig))))))))))
                            :<|> (Named
                                    '("iput", ValidateSAMLEmailsConfig)
                                    (Description ""
                                     :> (Summary "Put config for validateSAMLemails"
                                         :> (CanThrow ('MissingPermission 'Nothing)
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("validateSAMLemails"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      ValidateSAMLEmailsConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         ValidateSAMLEmailsConfig)))))))))))))
                                  :<|> Named
                                         '("ipatch", ValidateSAMLEmailsConfig)
                                         (Description ""
                                          :> (Summary "Patch config for validateSAMLemails"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow TeamFeatureError
                                                              :> (CanThrowMany '[]
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("validateSAMLemails"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        (LockableFeaturePatch
                                                                                           ValidateSAMLEmailsConfig)
                                                                                      :> Patch
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              ValidateSAMLEmailsConfig)))))))))))))))
                           :<|> ((Named
                                    '("iget", DigitalSignaturesConfig)
                                    (Description ""
                                     :> (Summary "Get config for digitalSignatures"
                                         :> (CanThrow ('MissingPermission 'Nothing)
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("digitalSignatures"
                                                                     :> Get
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             DigitalSignaturesConfig))))))))))
                                  :<|> (Named
                                          '("iput", DigitalSignaturesConfig)
                                          (Description ""
                                           :> (Summary "Put config for digitalSignatures"
                                               :> (CanThrow ('MissingPermission 'Nothing)
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("digitalSignatures"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            DigitalSignaturesConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               DigitalSignaturesConfig)))))))))))))
                                        :<|> Named
                                               '("ipatch", DigitalSignaturesConfig)
                                               (Description ""
                                                :> (Summary "Patch config for digitalSignatures"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> (CanThrowMany '[]
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("digitalSignatures"
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              (LockableFeaturePatch
                                                                                                 DigitalSignaturesConfig)
                                                                                            :> Patch
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    DigitalSignaturesConfig)))))))))))))))
                                 :<|> ((Named
                                          '("iget", AppLockConfig)
                                          (Description ""
                                           :> (Summary "Get config for appLock"
                                               :> (CanThrow ('MissingPermission 'Nothing)
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("appLock"
                                                                           :> Get
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   AppLockConfig))))))))))
                                        :<|> (Named
                                                '("iput", AppLockConfig)
                                                (Description ""
                                                 :> (Summary "Put config for appLock"
                                                     :> (CanThrow ('MissingPermission 'Nothing)
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("appLock"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  AppLockConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     AppLockConfig)))))))))))))
                                              :<|> Named
                                                     '("ipatch", AppLockConfig)
                                                     (Description ""
                                                      :> (Summary "Patch config for appLock"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany '[]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("appLock"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (LockableFeaturePatch
                                                                                                       AppLockConfig)
                                                                                                  :> Patch
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          AppLockConfig)))))))))))))))
                                       :<|> ((Named
                                                '("iget", FileSharingConfig)
                                                (Description ""
                                                 :> (Summary "Get config for fileSharing"
                                                     :> (CanThrow ('MissingPermission 'Nothing)
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("fileSharing"
                                                                                 :> Get
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         FileSharingConfig))))))))))
                                              :<|> (Named
                                                      '("iput", FileSharingConfig)
                                                      (Description ""
                                                       :> (Summary "Put config for fileSharing"
                                                           :> (CanThrow
                                                                 ('MissingPermission 'Nothing)
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("fileSharing"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        FileSharingConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           FileSharingConfig)))))))))))))
                                                    :<|> Named
                                                           '("ipatch", FileSharingConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Patch config for fileSharing"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("fileSharing"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (LockableFeaturePatch
                                                                                                             FileSharingConfig)
                                                                                                        :> Patch
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                FileSharingConfig)))))))))))))))
                                             :<|> (Named
                                                     '("iget", ClassifiedDomainsConfig)
                                                     (Description ""
                                                      :> (Summary "Get config for classifiedDomains"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("classifiedDomains"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              ClassifiedDomainsConfig))))))))))
                                                   :<|> ((Named
                                                            '("iget", ConferenceCallingConfig)
                                                            (Description ""
                                                             :> (Summary
                                                                   "Get config for conferenceCalling"
                                                                 :> (CanThrow
                                                                       ('MissingPermission 'Nothing)
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("conferenceCalling"
                                                                                             :> Get
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     ConferenceCallingConfig))))))))))
                                                          :<|> (Named
                                                                  '("iput", ConferenceCallingConfig)
                                                                  (Description ""
                                                                   :> (Summary
                                                                         "Put config for conferenceCalling"
                                                                       :> (CanThrow
                                                                             ('MissingPermission
                                                                                'Nothing)
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("conferenceCalling"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    ConferenceCallingConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       ConferenceCallingConfig)))))))))))))
                                                                :<|> Named
                                                                       '("ipatch",
                                                                         ConferenceCallingConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Patch config for conferenceCalling"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("conferenceCalling"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeaturePatch
                                                                                                                         ConferenceCallingConfig)
                                                                                                                    :> Patch
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            ConferenceCallingConfig)))))))))))))))
                                                         :<|> ((Named
                                                                  '("iget",
                                                                    SelfDeletingMessagesConfig)
                                                                  (Description ""
                                                                   :> (Summary
                                                                         "Get config for selfDeletingMessages"
                                                                       :> (CanThrow
                                                                             ('MissingPermission
                                                                                'Nothing)
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("selfDeletingMessages"
                                                                                                   :> Get
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           SelfDeletingMessagesConfig))))))))))
                                                                :<|> (Named
                                                                        '("iput",
                                                                          SelfDeletingMessagesConfig)
                                                                        (Description ""
                                                                         :> (Summary
                                                                               "Put config for selfDeletingMessages"
                                                                             :> (CanThrow
                                                                                   ('MissingPermission
                                                                                      'Nothing)
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("selfDeletingMessages"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          SelfDeletingMessagesConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             SelfDeletingMessagesConfig)))))))))))))
                                                                      :<|> Named
                                                                             '("ipatch",
                                                                               SelfDeletingMessagesConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Patch config for selfDeletingMessages"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("selfDeletingMessages"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeaturePatch
                                                                                                                               SelfDeletingMessagesConfig)
                                                                                                                          :> Patch
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  SelfDeletingMessagesConfig)))))))))))))))
                                                               :<|> ((Named
                                                                        '("iget", GuestLinksConfig)
                                                                        (Description ""
                                                                         :> (Summary
                                                                               "Get config for conversationGuestLinks"
                                                                             :> (CanThrow
                                                                                   ('MissingPermission
                                                                                      'Nothing)
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("conversationGuestLinks"
                                                                                                         :> Get
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 GuestLinksConfig))))))))))
                                                                      :<|> (Named
                                                                              '("iput",
                                                                                GuestLinksConfig)
                                                                              (Description ""
                                                                               :> (Summary
                                                                                     "Put config for conversationGuestLinks"
                                                                                   :> (CanThrow
                                                                                         ('MissingPermission
                                                                                            'Nothing)
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                GuestLinksConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   GuestLinksConfig)))))))))))))
                                                                            :<|> Named
                                                                                   '("ipatch",
                                                                                     GuestLinksConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Patch config for conversationGuestLinks"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("conversationGuestLinks"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeaturePatch
                                                                                                                                     GuestLinksConfig)
                                                                                                                                :> Patch
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        GuestLinksConfig)))))))))))))))
                                                                     :<|> ((Named
                                                                              '("iget",
                                                                                SndFactorPasswordChallengeConfig)
                                                                              (Description ""
                                                                               :> (Summary
                                                                                     "Get config for sndFactorPasswordChallenge"
                                                                                   :> (CanThrow
                                                                                         ('MissingPermission
                                                                                            'Nothing)
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                                               :> Get
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       SndFactorPasswordChallengeConfig))))))))))
                                                                            :<|> (Named
                                                                                    '("iput",
                                                                                      SndFactorPasswordChallengeConfig)
                                                                                    (Description ""
                                                                                     :> (Summary
                                                                                           "Put config for sndFactorPasswordChallenge"
                                                                                         :> (CanThrow
                                                                                               ('MissingPermission
                                                                                                  'Nothing)
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           TeamFeatureError
                                                                                                         :> (CanThrowMany
                                                                                                               '[]
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   (Feature
                                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                                 :> Put
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         SndFactorPasswordChallengeConfig)))))))))))))
                                                                                  :<|> Named
                                                                                         '("ipatch",
                                                                                           SndFactorPasswordChallengeConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Patch config for sndFactorPasswordChallenge"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("sndFactorPasswordChallenge"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeaturePatch
                                                                                                                                           SndFactorPasswordChallengeConfig)
                                                                                                                                      :> Patch
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              SndFactorPasswordChallengeConfig)))))))))))))))
                                                                           :<|> ((Named
                                                                                    '("iget",
                                                                                      MLSConfig)
                                                                                    (Description ""
                                                                                     :> (Summary
                                                                                           "Get config for mls"
                                                                                         :> (CanThrow
                                                                                               ('MissingPermission
                                                                                                  'Nothing)
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("mls"
                                                                                                                     :> Get
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             MLSConfig))))))))))
                                                                                  :<|> (Named
                                                                                          '("iput",
                                                                                            MLSConfig)
                                                                                          (Description
                                                                                             ""
                                                                                           :> (Summary
                                                                                                 "Put config for mls"
                                                                                               :> (CanThrow
                                                                                                     ('MissingPermission
                                                                                                        'Nothing)
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> (CanThrow
                                                                                                                 TeamFeatureError
                                                                                                               :> (CanThrowMany
                                                                                                                     '[]
                                                                                                                   :> ("teams"
                                                                                                                       :> (Capture
                                                                                                                             "tid"
                                                                                                                             TeamId
                                                                                                                           :> ("features"
                                                                                                                               :> ("mls"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         (Feature
                                                                                                                                            MLSConfig)
                                                                                                                                       :> Put
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               MLSConfig)))))))))))))
                                                                                        :<|> Named
                                                                                               '("ipatch",
                                                                                                 MLSConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Patch config for mls"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("mls"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeaturePatch
                                                                                                                                                 MLSConfig)
                                                                                                                                            :> Patch
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    MLSConfig)))))))))))))))
                                                                                 :<|> ((Named
                                                                                          '("iget",
                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                          (Description
                                                                                             ""
                                                                                           :> (Summary
                                                                                                 "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                               :> (CanThrow
                                                                                                     ('MissingPermission
                                                                                                        'Nothing)
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                           :> Get
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                        :<|> (Named
                                                                                                '("iput",
                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                                (Description
                                                                                                   ""
                                                                                                 :> (Summary
                                                                                                       "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                     :> (CanThrow
                                                                                                           ('MissingPermission
                                                                                                              'Nothing)
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       TeamFeatureError
                                                                                                                     :> (CanThrowMany
                                                                                                                           '[]
                                                                                                                         :> ("teams"
                                                                                                                             :> (Capture
                                                                                                                                   "tid"
                                                                                                                                   TeamId
                                                                                                                                 :> ("features"
                                                                                                                                     :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               (Feature
                                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                             :> Put
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                              :<|> Named
                                                                                                     '("ipatch",
                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeaturePatch
                                                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                  :> Patch
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                       :<|> ((Named
                                                                                                '("iget",
                                                                                                  OutlookCalIntegrationConfig)
                                                                                                (Description
                                                                                                   ""
                                                                                                 :> (Summary
                                                                                                       "Get config for outlookCalIntegration"
                                                                                                     :> (CanThrow
                                                                                                           ('MissingPermission
                                                                                                              'Nothing)
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("outlookCalIntegration"
                                                                                                                                 :> Get
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         OutlookCalIntegrationConfig))))))))))
                                                                                              :<|> (Named
                                                                                                      '("iput",
                                                                                                        OutlookCalIntegrationConfig)
                                                                                                      (Description
                                                                                                         ""
                                                                                                       :> (Summary
                                                                                                             "Put config for outlookCalIntegration"
                                                                                                           :> (CanThrow
                                                                                                                 ('MissingPermission
                                                                                                                    'Nothing)
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             TeamFeatureError
                                                                                                                           :> (CanThrowMany
                                                                                                                                 '[]
                                                                                                                               :> ("teams"
                                                                                                                                   :> (Capture
                                                                                                                                         "tid"
                                                                                                                                         TeamId
                                                                                                                                       :> ("features"
                                                                                                                                           :> ("outlookCalIntegration"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     (Feature
                                                                                                                                                        OutlookCalIntegrationConfig)
                                                                                                                                                   :> Put
                                                                                                                                                        '[JSON]
                                                                                                                                                        (LockableFeature
                                                                                                                                                           OutlookCalIntegrationConfig)))))))))))))
                                                                                                    :<|> Named
                                                                                                           '("ipatch",
                                                                                                             OutlookCalIntegrationConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Patch config for outlookCalIntegration"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("outlookCalIntegration"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeaturePatch
                                                                                                                                                             OutlookCalIntegrationConfig)
                                                                                                                                                        :> Patch
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                OutlookCalIntegrationConfig)))))))))))))))
                                                                                             :<|> ((Named
                                                                                                      '("iget",
                                                                                                        MlsE2EIdConfig)
                                                                                                      (Description
                                                                                                         ""
                                                                                                       :> (Summary
                                                                                                             "Get config for mlsE2EId"
                                                                                                           :> (CanThrow
                                                                                                                 ('MissingPermission
                                                                                                                    'Nothing)
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("mlsE2EId"
                                                                                                                                       :> Get
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               MlsE2EIdConfig))))))))))
                                                                                                    :<|> (Named
                                                                                                            '("iput",
                                                                                                              MlsE2EIdConfig)
                                                                                                            (Description
                                                                                                               ""
                                                                                                             :> (Summary
                                                                                                                   "Put config for mlsE2EId"
                                                                                                                 :> (CanThrow
                                                                                                                       ('MissingPermission
                                                                                                                          'Nothing)
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   TeamFeatureError
                                                                                                                                 :> (CanThrowMany
                                                                                                                                       '[]
                                                                                                                                     :> ("teams"
                                                                                                                                         :> (Capture
                                                                                                                                               "tid"
                                                                                                                                               TeamId
                                                                                                                                             :> ("features"
                                                                                                                                                 :> ("mlsE2EId"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           (Feature
                                                                                                                                                              MlsE2EIdConfig)
                                                                                                                                                         :> Put
                                                                                                                                                              '[JSON]
                                                                                                                                                              (LockableFeature
                                                                                                                                                                 MlsE2EIdConfig)))))))))))))
                                                                                                          :<|> Named
                                                                                                                 '("ipatch",
                                                                                                                   MlsE2EIdConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Patch config for mlsE2EId"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("mlsE2EId"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeaturePatch
                                                                                                                                                                   MlsE2EIdConfig)
                                                                                                                                                              :> Patch
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      MlsE2EIdConfig)))))))))))))))
                                                                                                   :<|> ((Named
                                                                                                            '("iget",
                                                                                                              MlsMigrationConfig)
                                                                                                            (Description
                                                                                                               ""
                                                                                                             :> (Summary
                                                                                                                   "Get config for mlsMigration"
                                                                                                                 :> (CanThrow
                                                                                                                       ('MissingPermission
                                                                                                                          'Nothing)
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamNotFound
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("mlsMigration"
                                                                                                                                             :> Get
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     MlsMigrationConfig))))))))))
                                                                                                          :<|> (Named
                                                                                                                  '("iput",
                                                                                                                    MlsMigrationConfig)
                                                                                                                  (Description
                                                                                                                     ""
                                                                                                                   :> (Summary
                                                                                                                         "Put config for mlsMigration"
                                                                                                                       :> (CanThrow
                                                                                                                             ('MissingPermission
                                                                                                                                'Nothing)
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'TeamNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         TeamFeatureError
                                                                                                                                       :> (CanThrowMany
                                                                                                                                             '[]
                                                                                                                                           :> ("teams"
                                                                                                                                               :> (Capture
                                                                                                                                                     "tid"
                                                                                                                                                     TeamId
                                                                                                                                                   :> ("features"
                                                                                                                                                       :> ("mlsMigration"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 (Feature
                                                                                                                                                                    MlsMigrationConfig)
                                                                                                                                                               :> Put
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (LockableFeature
                                                                                                                                                                       MlsMigrationConfig)))))))))))))
                                                                                                                :<|> Named
                                                                                                                       '("ipatch",
                                                                                                                         MlsMigrationConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Patch config for mlsMigration"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("mlsMigration"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeaturePatch
                                                                                                                                                                         MlsMigrationConfig)
                                                                                                                                                                    :> Patch
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MlsMigrationConfig)))))))))))))))
                                                                                                         :<|> ((Named
                                                                                                                  '("iget",
                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                  (Description
                                                                                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                   :> (Summary
                                                                                                                         "Get config for enforceFileDownloadLocation"
                                                                                                                       :> (CanThrow
                                                                                                                             ('MissingPermission
                                                                                                                                'Nothing)
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'TeamNotFound
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("enforceFileDownloadLocation"
                                                                                                                                                   :> Get
                                                                                                                                                        '[JSON]
                                                                                                                                                        (LockableFeature
                                                                                                                                                           EnforceFileDownloadLocationConfig))))))))))
                                                                                                                :<|> (Named
                                                                                                                        '("iput",
                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                        (Description
                                                                                                                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                         :> (Summary
                                                                                                                               "Put config for enforceFileDownloadLocation"
                                                                                                                             :> (CanThrow
                                                                                                                                   ('MissingPermission
                                                                                                                                      'Nothing)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TeamNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               TeamFeatureError
                                                                                                                                             :> (CanThrowMany
                                                                                                                                                   '[]
                                                                                                                                                 :> ("teams"
                                                                                                                                                     :> (Capture
                                                                                                                                                           "tid"
                                                                                                                                                           TeamId
                                                                                                                                                         :> ("features"
                                                                                                                                                             :> ("enforceFileDownloadLocation"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       (Feature
                                                                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                                                                     :> Put
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          (LockableFeature
                                                                                                                                                                             EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                      :<|> Named
                                                                                                                             '("ipatch",
                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                             (Description
                                                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                              :> (Summary
                                                                                                                                    "Patch config for enforceFileDownloadLocation"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeaturePatch
                                                                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                                                                          :> Patch
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iget",
                                                                                                                         LimitedEventFanoutConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for limitedEventFanout"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("limitedEventFanout"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                LimitedEventFanoutConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               LimitedEventFanoutConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for limitedEventFanout"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("limitedEventFanout"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               LimitedEventFanoutConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  LimitedEventFanoutConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for limitedEventFanout"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("limitedEventFanout"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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 (IAllFeaturesAPI Features) GalleyEffects
allFeaturesAPI
    -- legacy endpoints
    API
  ((Named
      '("iget", LegalholdConfig)
      (Description ""
       :> (Summary "Get config for legalhold"
           :> (CanThrow ('MissingPermission 'Nothing)
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow 'TeamNotFound
                       :> ("teams"
                           :> (Capture "tid" TeamId
                               :> ("features"
                                   :> ("legalhold"
                                       :> Get '[JSON] (LockableFeature LegalholdConfig))))))))))
    :<|> (Named
            '("iput", LegalholdConfig)
            (Description ""
             :> (Summary "Put config for legalhold"
                 :> (CanThrow ('MissingPermission 'Nothing)
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> (CanThrow TeamFeatureError
                                 :> (CanThrowMany
                                       '[ 'ActionDenied 'RemoveConversationMember,
                                          'CannotEnableLegalHoldServiceLargeTeam,
                                          'LegalHoldNotEnabled, 'LegalHoldDisableUnimplemented,
                                          'LegalHoldServiceNotRegistered,
                                          'UserLegalHoldIllegalOperation,
                                          'LegalHoldCouldNotBlockConnections]
                                     :> ("teams"
                                         :> (Capture "tid" TeamId
                                             :> ("features"
                                                 :> ("legalhold"
                                                     :> (ReqBody '[JSON] (Feature LegalholdConfig)
                                                         :> Put
                                                              '[JSON]
                                                              (LockableFeature
                                                                 LegalholdConfig)))))))))))))
          :<|> Named
                 '("ipatch", LegalholdConfig)
                 (Description ""
                  :> (Summary "Patch config for legalhold"
                      :> (CanThrow ('MissingPermission 'Nothing)
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> (CanThrow TeamFeatureError
                                      :> (CanThrowMany
                                            '[ 'ActionDenied 'RemoveConversationMember,
                                               'CannotEnableLegalHoldServiceLargeTeam,
                                               'LegalHoldNotEnabled, 'LegalHoldDisableUnimplemented,
                                               'LegalHoldServiceNotRegistered,
                                               'UserLegalHoldIllegalOperation,
                                               'LegalHoldCouldNotBlockConnections]
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("legalhold"
                                                          :> (ReqBody
                                                                '[JSON]
                                                                (LockableFeaturePatch
                                                                   LegalholdConfig)
                                                              :> Patch
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      LegalholdConfig)))))))))))))))
   :<|> ((Named
            '("iget", SSOConfig)
            (Description ""
             :> (Summary "Get config for sso"
                 :> (CanThrow ('MissingPermission 'Nothing)
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features"
                                         :> ("sso"
                                             :> Get '[JSON] (LockableFeature SSOConfig))))))))))
          :<|> (Named
                  '("iput", SSOConfig)
                  (Description ""
                   :> (Summary "Put config for sso"
                       :> (CanThrow ('MissingPermission 'Nothing)
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("sso"
                                                           :> (ReqBody '[JSON] (Feature SSOConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       SSOConfig)))))))))))))
                :<|> Named
                       '("ipatch", SSOConfig)
                       (Description ""
                        :> (Summary "Patch config for sso"
                            :> (CanThrow ('MissingPermission 'Nothing)
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> (CanThrow TeamFeatureError
                                            :> (CanThrowMany '[]
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("sso"
                                                                :> (ReqBody
                                                                      '[JSON]
                                                                      (LockableFeaturePatch
                                                                         SSOConfig)
                                                                    :> Patch
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            SSOConfig)))))))))))))))
         :<|> ((Named
                  '("iget", SearchVisibilityAvailableConfig)
                  (Description ""
                   :> (Summary "Get config for searchVisibility"
                       :> (CanThrow ('MissingPermission 'Nothing)
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> ("teams"
                                       :> (Capture "tid" TeamId
                                           :> ("features"
                                               :> ("searchVisibility"
                                                   :> Get
                                                        '[JSON]
                                                        (LockableFeature
                                                           SearchVisibilityAvailableConfig))))))))))
                :<|> (Named
                        '("iput", SearchVisibilityAvailableConfig)
                        (Description ""
                         :> (Summary "Put config for searchVisibility"
                             :> (CanThrow ('MissingPermission 'Nothing)
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("searchVisibility"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          SearchVisibilityAvailableConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             SearchVisibilityAvailableConfig)))))))))))))
                      :<|> Named
                             '("ipatch", SearchVisibilityAvailableConfig)
                             (Description ""
                              :> (Summary "Patch config for searchVisibility"
                                  :> (CanThrow ('MissingPermission 'Nothing)
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> (CanThrow TeamFeatureError
                                                  :> (CanThrowMany '[]
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("searchVisibility"
                                                                      :> (ReqBody
                                                                            '[JSON]
                                                                            (LockableFeaturePatch
                                                                               SearchVisibilityAvailableConfig)
                                                                          :> Patch
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  SearchVisibilityAvailableConfig)))))))))))))))
               :<|> ((Named
                        '("iget", SearchVisibilityInboundConfig)
                        (Description ""
                         :> (Summary "Get config for searchVisibilityInbound"
                             :> (CanThrow ('MissingPermission 'Nothing)
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("searchVisibilityInbound"
                                                         :> Get
                                                              '[JSON]
                                                              (LockableFeature
                                                                 SearchVisibilityInboundConfig))))))))))
                      :<|> (Named
                              '("iput", SearchVisibilityInboundConfig)
                              (Description ""
                               :> (Summary "Put config for searchVisibilityInbound"
                                   :> (CanThrow ('MissingPermission 'Nothing)
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("searchVisibilityInbound"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                SearchVisibilityInboundConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   SearchVisibilityInboundConfig)))))))))))))
                            :<|> Named
                                   '("ipatch", SearchVisibilityInboundConfig)
                                   (Description ""
                                    :> (Summary "Patch config for searchVisibilityInbound"
                                        :> (CanThrow ('MissingPermission 'Nothing)
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> (CanThrow TeamFeatureError
                                                        :> (CanThrowMany '[]
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("searchVisibilityInbound"
                                                                            :> (ReqBody
                                                                                  '[JSON]
                                                                                  (LockableFeaturePatch
                                                                                     SearchVisibilityInboundConfig)
                                                                                :> Patch
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SearchVisibilityInboundConfig)))))))))))))))
                     :<|> ((Named
                              '("iget", ValidateSAMLEmailsConfig)
                              (Description ""
                               :> (Summary "Get config for validateSAMLemails"
                                   :> (CanThrow ('MissingPermission 'Nothing)
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("validateSAMLemails"
                                                               :> Get
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       ValidateSAMLEmailsConfig))))))))))
                            :<|> (Named
                                    '("iput", ValidateSAMLEmailsConfig)
                                    (Description ""
                                     :> (Summary "Put config for validateSAMLemails"
                                         :> (CanThrow ('MissingPermission 'Nothing)
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("validateSAMLemails"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      ValidateSAMLEmailsConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         ValidateSAMLEmailsConfig)))))))))))))
                                  :<|> Named
                                         '("ipatch", ValidateSAMLEmailsConfig)
                                         (Description ""
                                          :> (Summary "Patch config for validateSAMLemails"
                                              :> (CanThrow ('MissingPermission 'Nothing)
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow TeamFeatureError
                                                              :> (CanThrowMany '[]
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("validateSAMLemails"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        (LockableFeaturePatch
                                                                                           ValidateSAMLEmailsConfig)
                                                                                      :> Patch
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              ValidateSAMLEmailsConfig)))))))))))))))
                           :<|> ((Named
                                    '("iget", DigitalSignaturesConfig)
                                    (Description ""
                                     :> (Summary "Get config for digitalSignatures"
                                         :> (CanThrow ('MissingPermission 'Nothing)
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("digitalSignatures"
                                                                     :> Get
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             DigitalSignaturesConfig))))))))))
                                  :<|> (Named
                                          '("iput", DigitalSignaturesConfig)
                                          (Description ""
                                           :> (Summary "Put config for digitalSignatures"
                                               :> (CanThrow ('MissingPermission 'Nothing)
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("digitalSignatures"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            DigitalSignaturesConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               DigitalSignaturesConfig)))))))))))))
                                        :<|> Named
                                               '("ipatch", DigitalSignaturesConfig)
                                               (Description ""
                                                :> (Summary "Patch config for digitalSignatures"
                                                    :> (CanThrow ('MissingPermission 'Nothing)
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> (CanThrowMany '[]
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("digitalSignatures"
                                                                                        :> (ReqBody
                                                                                              '[JSON]
                                                                                              (LockableFeaturePatch
                                                                                                 DigitalSignaturesConfig)
                                                                                            :> Patch
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    DigitalSignaturesConfig)))))))))))))))
                                 :<|> ((Named
                                          '("iget", AppLockConfig)
                                          (Description ""
                                           :> (Summary "Get config for appLock"
                                               :> (CanThrow ('MissingPermission 'Nothing)
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("appLock"
                                                                           :> Get
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   AppLockConfig))))))))))
                                        :<|> (Named
                                                '("iput", AppLockConfig)
                                                (Description ""
                                                 :> (Summary "Put config for appLock"
                                                     :> (CanThrow ('MissingPermission 'Nothing)
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("appLock"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  AppLockConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     AppLockConfig)))))))))))))
                                              :<|> Named
                                                     '("ipatch", AppLockConfig)
                                                     (Description ""
                                                      :> (Summary "Patch config for appLock"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> (CanThrowMany '[]
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("appLock"
                                                                                              :> (ReqBody
                                                                                                    '[JSON]
                                                                                                    (LockableFeaturePatch
                                                                                                       AppLockConfig)
                                                                                                  :> Patch
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          AppLockConfig)))))))))))))))
                                       :<|> ((Named
                                                '("iget", FileSharingConfig)
                                                (Description ""
                                                 :> (Summary "Get config for fileSharing"
                                                     :> (CanThrow ('MissingPermission 'Nothing)
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("fileSharing"
                                                                                 :> Get
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         FileSharingConfig))))))))))
                                              :<|> (Named
                                                      '("iput", FileSharingConfig)
                                                      (Description ""
                                                       :> (Summary "Put config for fileSharing"
                                                           :> (CanThrow
                                                                 ('MissingPermission 'Nothing)
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("fileSharing"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        FileSharingConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           FileSharingConfig)))))))))))))
                                                    :<|> Named
                                                           '("ipatch", FileSharingConfig)
                                                           (Description ""
                                                            :> (Summary
                                                                  "Patch config for fileSharing"
                                                                :> (CanThrow
                                                                      ('MissingPermission 'Nothing)
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> (CanThrowMany '[]
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("fileSharing"
                                                                                                    :> (ReqBody
                                                                                                          '[JSON]
                                                                                                          (LockableFeaturePatch
                                                                                                             FileSharingConfig)
                                                                                                        :> Patch
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                FileSharingConfig)))))))))))))))
                                             :<|> (Named
                                                     '("iget", ClassifiedDomainsConfig)
                                                     (Description ""
                                                      :> (Summary "Get config for classifiedDomains"
                                                          :> (CanThrow ('MissingPermission 'Nothing)
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("classifiedDomains"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              ClassifiedDomainsConfig))))))))))
                                                   :<|> ((Named
                                                            '("iget", ConferenceCallingConfig)
                                                            (Description ""
                                                             :> (Summary
                                                                   "Get config for conferenceCalling"
                                                                 :> (CanThrow
                                                                       ('MissingPermission 'Nothing)
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("conferenceCalling"
                                                                                             :> Get
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     ConferenceCallingConfig))))))))))
                                                          :<|> (Named
                                                                  '("iput", ConferenceCallingConfig)
                                                                  (Description ""
                                                                   :> (Summary
                                                                         "Put config for conferenceCalling"
                                                                       :> (CanThrow
                                                                             ('MissingPermission
                                                                                'Nothing)
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("conferenceCalling"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    ConferenceCallingConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       ConferenceCallingConfig)))))))))))))
                                                                :<|> Named
                                                                       '("ipatch",
                                                                         ConferenceCallingConfig)
                                                                       (Description ""
                                                                        :> (Summary
                                                                              "Patch config for conferenceCalling"
                                                                            :> (CanThrow
                                                                                  ('MissingPermission
                                                                                     'Nothing)
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> (CanThrowMany
                                                                                                  '[]
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("conferenceCalling"
                                                                                                                :> (ReqBody
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeaturePatch
                                                                                                                         ConferenceCallingConfig)
                                                                                                                    :> Patch
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            ConferenceCallingConfig)))))))))))))))
                                                         :<|> ((Named
                                                                  '("iget",
                                                                    SelfDeletingMessagesConfig)
                                                                  (Description ""
                                                                   :> (Summary
                                                                         "Get config for selfDeletingMessages"
                                                                       :> (CanThrow
                                                                             ('MissingPermission
                                                                                'Nothing)
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("selfDeletingMessages"
                                                                                                   :> Get
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           SelfDeletingMessagesConfig))))))))))
                                                                :<|> (Named
                                                                        '("iput",
                                                                          SelfDeletingMessagesConfig)
                                                                        (Description ""
                                                                         :> (Summary
                                                                               "Put config for selfDeletingMessages"
                                                                             :> (CanThrow
                                                                                   ('MissingPermission
                                                                                      'Nothing)
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("selfDeletingMessages"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          SelfDeletingMessagesConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             SelfDeletingMessagesConfig)))))))))))))
                                                                      :<|> Named
                                                                             '("ipatch",
                                                                               SelfDeletingMessagesConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Patch config for selfDeletingMessages"
                                                                                  :> (CanThrow
                                                                                        ('MissingPermission
                                                                                           'Nothing)
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> (CanThrowMany
                                                                                                        '[]
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("selfDeletingMessages"
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeaturePatch
                                                                                                                               SelfDeletingMessagesConfig)
                                                                                                                          :> Patch
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  SelfDeletingMessagesConfig)))))))))))))))
                                                               :<|> ((Named
                                                                        '("iget", GuestLinksConfig)
                                                                        (Description ""
                                                                         :> (Summary
                                                                               "Get config for conversationGuestLinks"
                                                                             :> (CanThrow
                                                                                   ('MissingPermission
                                                                                      'Nothing)
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("conversationGuestLinks"
                                                                                                         :> Get
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 GuestLinksConfig))))))))))
                                                                      :<|> (Named
                                                                              '("iput",
                                                                                GuestLinksConfig)
                                                                              (Description ""
                                                                               :> (Summary
                                                                                     "Put config for conversationGuestLinks"
                                                                                   :> (CanThrow
                                                                                         ('MissingPermission
                                                                                            'Nothing)
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                GuestLinksConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   GuestLinksConfig)))))))))))))
                                                                            :<|> Named
                                                                                   '("ipatch",
                                                                                     GuestLinksConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Patch config for conversationGuestLinks"
                                                                                        :> (CanThrow
                                                                                              ('MissingPermission
                                                                                                 'Nothing)
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("conversationGuestLinks"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeaturePatch
                                                                                                                                     GuestLinksConfig)
                                                                                                                                :> Patch
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        GuestLinksConfig)))))))))))))))
                                                                     :<|> ((Named
                                                                              '("iget",
                                                                                SndFactorPasswordChallengeConfig)
                                                                              (Description ""
                                                                               :> (Summary
                                                                                     "Get config for sndFactorPasswordChallenge"
                                                                                   :> (CanThrow
                                                                                         ('MissingPermission
                                                                                            'Nothing)
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                                               :> Get
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       SndFactorPasswordChallengeConfig))))))))))
                                                                            :<|> (Named
                                                                                    '("iput",
                                                                                      SndFactorPasswordChallengeConfig)
                                                                                    (Description ""
                                                                                     :> (Summary
                                                                                           "Put config for sndFactorPasswordChallenge"
                                                                                         :> (CanThrow
                                                                                               ('MissingPermission
                                                                                                  'Nothing)
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           TeamFeatureError
                                                                                                         :> (CanThrowMany
                                                                                                               '[]
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   (Feature
                                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                                 :> Put
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         SndFactorPasswordChallengeConfig)))))))))))))
                                                                                  :<|> Named
                                                                                         '("ipatch",
                                                                                           SndFactorPasswordChallengeConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Patch config for sndFactorPasswordChallenge"
                                                                                              :> (CanThrow
                                                                                                    ('MissingPermission
                                                                                                       'Nothing)
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("sndFactorPasswordChallenge"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeaturePatch
                                                                                                                                           SndFactorPasswordChallengeConfig)
                                                                                                                                      :> Patch
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              SndFactorPasswordChallengeConfig)))))))))))))))
                                                                           :<|> ((Named
                                                                                    '("iget",
                                                                                      MLSConfig)
                                                                                    (Description ""
                                                                                     :> (Summary
                                                                                           "Get config for mls"
                                                                                         :> (CanThrow
                                                                                               ('MissingPermission
                                                                                                  'Nothing)
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("mls"
                                                                                                                     :> Get
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             MLSConfig))))))))))
                                                                                  :<|> (Named
                                                                                          '("iput",
                                                                                            MLSConfig)
                                                                                          (Description
                                                                                             ""
                                                                                           :> (Summary
                                                                                                 "Put config for mls"
                                                                                               :> (CanThrow
                                                                                                     ('MissingPermission
                                                                                                        'Nothing)
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> (CanThrow
                                                                                                                 TeamFeatureError
                                                                                                               :> (CanThrowMany
                                                                                                                     '[]
                                                                                                                   :> ("teams"
                                                                                                                       :> (Capture
                                                                                                                             "tid"
                                                                                                                             TeamId
                                                                                                                           :> ("features"
                                                                                                                               :> ("mls"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         (Feature
                                                                                                                                            MLSConfig)
                                                                                                                                       :> Put
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               MLSConfig)))))))))))))
                                                                                        :<|> Named
                                                                                               '("ipatch",
                                                                                                 MLSConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Patch config for mls"
                                                                                                    :> (CanThrow
                                                                                                          ('MissingPermission
                                                                                                             'Nothing)
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("mls"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeaturePatch
                                                                                                                                                 MLSConfig)
                                                                                                                                            :> Patch
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    MLSConfig)))))))))))))))
                                                                                 :<|> ((Named
                                                                                          '("iget",
                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                          (Description
                                                                                             ""
                                                                                           :> (Summary
                                                                                                 "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                               :> (CanThrow
                                                                                                     ('MissingPermission
                                                                                                        'Nothing)
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                           :> Get
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                        :<|> (Named
                                                                                                '("iput",
                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                                (Description
                                                                                                   ""
                                                                                                 :> (Summary
                                                                                                       "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                     :> (CanThrow
                                                                                                           ('MissingPermission
                                                                                                              'Nothing)
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       TeamFeatureError
                                                                                                                     :> (CanThrowMany
                                                                                                                           '[]
                                                                                                                         :> ("teams"
                                                                                                                             :> (Capture
                                                                                                                                   "tid"
                                                                                                                                   TeamId
                                                                                                                                 :> ("features"
                                                                                                                                     :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               (Feature
                                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                             :> Put
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                              :<|> Named
                                                                                                     '("ipatch",
                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                          :> (CanThrow
                                                                                                                ('MissingPermission
                                                                                                                   'Nothing)
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeaturePatch
                                                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                  :> Patch
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                       :<|> ((Named
                                                                                                '("iget",
                                                                                                  OutlookCalIntegrationConfig)
                                                                                                (Description
                                                                                                   ""
                                                                                                 :> (Summary
                                                                                                       "Get config for outlookCalIntegration"
                                                                                                     :> (CanThrow
                                                                                                           ('MissingPermission
                                                                                                              'Nothing)
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("outlookCalIntegration"
                                                                                                                                 :> Get
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         OutlookCalIntegrationConfig))))))))))
                                                                                              :<|> (Named
                                                                                                      '("iput",
                                                                                                        OutlookCalIntegrationConfig)
                                                                                                      (Description
                                                                                                         ""
                                                                                                       :> (Summary
                                                                                                             "Put config for outlookCalIntegration"
                                                                                                           :> (CanThrow
                                                                                                                 ('MissingPermission
                                                                                                                    'Nothing)
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             TeamFeatureError
                                                                                                                           :> (CanThrowMany
                                                                                                                                 '[]
                                                                                                                               :> ("teams"
                                                                                                                                   :> (Capture
                                                                                                                                         "tid"
                                                                                                                                         TeamId
                                                                                                                                       :> ("features"
                                                                                                                                           :> ("outlookCalIntegration"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     (Feature
                                                                                                                                                        OutlookCalIntegrationConfig)
                                                                                                                                                   :> Put
                                                                                                                                                        '[JSON]
                                                                                                                                                        (LockableFeature
                                                                                                                                                           OutlookCalIntegrationConfig)))))))))))))
                                                                                                    :<|> Named
                                                                                                           '("ipatch",
                                                                                                             OutlookCalIntegrationConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Patch config for outlookCalIntegration"
                                                                                                                :> (CanThrow
                                                                                                                      ('MissingPermission
                                                                                                                         'Nothing)
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("outlookCalIntegration"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeaturePatch
                                                                                                                                                             OutlookCalIntegrationConfig)
                                                                                                                                                        :> Patch
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                OutlookCalIntegrationConfig)))))))))))))))
                                                                                             :<|> ((Named
                                                                                                      '("iget",
                                                                                                        MlsE2EIdConfig)
                                                                                                      (Description
                                                                                                         ""
                                                                                                       :> (Summary
                                                                                                             "Get config for mlsE2EId"
                                                                                                           :> (CanThrow
                                                                                                                 ('MissingPermission
                                                                                                                    'Nothing)
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("mlsE2EId"
                                                                                                                                       :> Get
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               MlsE2EIdConfig))))))))))
                                                                                                    :<|> (Named
                                                                                                            '("iput",
                                                                                                              MlsE2EIdConfig)
                                                                                                            (Description
                                                                                                               ""
                                                                                                             :> (Summary
                                                                                                                   "Put config for mlsE2EId"
                                                                                                                 :> (CanThrow
                                                                                                                       ('MissingPermission
                                                                                                                          'Nothing)
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   TeamFeatureError
                                                                                                                                 :> (CanThrowMany
                                                                                                                                       '[]
                                                                                                                                     :> ("teams"
                                                                                                                                         :> (Capture
                                                                                                                                               "tid"
                                                                                                                                               TeamId
                                                                                                                                             :> ("features"
                                                                                                                                                 :> ("mlsE2EId"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           (Feature
                                                                                                                                                              MlsE2EIdConfig)
                                                                                                                                                         :> Put
                                                                                                                                                              '[JSON]
                                                                                                                                                              (LockableFeature
                                                                                                                                                                 MlsE2EIdConfig)))))))))))))
                                                                                                          :<|> Named
                                                                                                                 '("ipatch",
                                                                                                                   MlsE2EIdConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Patch config for mlsE2EId"
                                                                                                                      :> (CanThrow
                                                                                                                            ('MissingPermission
                                                                                                                               'Nothing)
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("mlsE2EId"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeaturePatch
                                                                                                                                                                   MlsE2EIdConfig)
                                                                                                                                                              :> Patch
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      MlsE2EIdConfig)))))))))))))))
                                                                                                   :<|> ((Named
                                                                                                            '("iget",
                                                                                                              MlsMigrationConfig)
                                                                                                            (Description
                                                                                                               ""
                                                                                                             :> (Summary
                                                                                                                   "Get config for mlsMigration"
                                                                                                                 :> (CanThrow
                                                                                                                       ('MissingPermission
                                                                                                                          'Nothing)
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamNotFound
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("mlsMigration"
                                                                                                                                             :> Get
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     MlsMigrationConfig))))))))))
                                                                                                          :<|> (Named
                                                                                                                  '("iput",
                                                                                                                    MlsMigrationConfig)
                                                                                                                  (Description
                                                                                                                     ""
                                                                                                                   :> (Summary
                                                                                                                         "Put config for mlsMigration"
                                                                                                                       :> (CanThrow
                                                                                                                             ('MissingPermission
                                                                                                                                'Nothing)
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'TeamNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         TeamFeatureError
                                                                                                                                       :> (CanThrowMany
                                                                                                                                             '[]
                                                                                                                                           :> ("teams"
                                                                                                                                               :> (Capture
                                                                                                                                                     "tid"
                                                                                                                                                     TeamId
                                                                                                                                                   :> ("features"
                                                                                                                                                       :> ("mlsMigration"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 (Feature
                                                                                                                                                                    MlsMigrationConfig)
                                                                                                                                                               :> Put
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (LockableFeature
                                                                                                                                                                       MlsMigrationConfig)))))))))))))
                                                                                                                :<|> Named
                                                                                                                       '("ipatch",
                                                                                                                         MlsMigrationConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Patch config for mlsMigration"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("mlsMigration"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeaturePatch
                                                                                                                                                                         MlsMigrationConfig)
                                                                                                                                                                    :> Patch
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MlsMigrationConfig)))))))))))))))
                                                                                                         :<|> ((Named
                                                                                                                  '("iget",
                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                  (Description
                                                                                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                   :> (Summary
                                                                                                                         "Get config for enforceFileDownloadLocation"
                                                                                                                       :> (CanThrow
                                                                                                                             ('MissingPermission
                                                                                                                                'Nothing)
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'TeamNotFound
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("enforceFileDownloadLocation"
                                                                                                                                                   :> Get
                                                                                                                                                        '[JSON]
                                                                                                                                                        (LockableFeature
                                                                                                                                                           EnforceFileDownloadLocationConfig))))))))))
                                                                                                                :<|> (Named
                                                                                                                        '("iput",
                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                        (Description
                                                                                                                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                         :> (Summary
                                                                                                                               "Put config for enforceFileDownloadLocation"
                                                                                                                             :> (CanThrow
                                                                                                                                   ('MissingPermission
                                                                                                                                      'Nothing)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TeamNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               TeamFeatureError
                                                                                                                                             :> (CanThrowMany
                                                                                                                                                   '[]
                                                                                                                                                 :> ("teams"
                                                                                                                                                     :> (Capture
                                                                                                                                                           "tid"
                                                                                                                                                           TeamId
                                                                                                                                                         :> ("features"
                                                                                                                                                             :> ("enforceFileDownloadLocation"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       (Feature
                                                                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                                                                     :> Put
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          (LockableFeature
                                                                                                                                                                             EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                      :<|> Named
                                                                                                                             '("ipatch",
                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                             (Description
                                                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                              :> (Summary
                                                                                                                                    "Patch config for enforceFileDownloadLocation"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeaturePatch
                                                                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                                                                          :> Patch
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                               :<|> (Named
                                                                                                                       '("iget",
                                                                                                                         LimitedEventFanoutConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Get config for limitedEventFanout"
                                                                                                                            :> (CanThrow
                                                                                                                                  ('MissingPermission
                                                                                                                                     'Nothing)
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("limitedEventFanout"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                LimitedEventFanoutConfig))))))))))
                                                                                                                     :<|> (Named
                                                                                                                             '("iput",
                                                                                                                               LimitedEventFanoutConfig)
                                                                                                                             (Description
                                                                                                                                ""
                                                                                                                              :> (Summary
                                                                                                                                    "Put config for limitedEventFanout"
                                                                                                                                  :> (CanThrow
                                                                                                                                        ('MissingPermission
                                                                                                                                           'Nothing)
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                        '[]
                                                                                                                                                      :> ("teams"
                                                                                                                                                          :> (Capture
                                                                                                                                                                "tid"
                                                                                                                                                                TeamId
                                                                                                                                                              :> ("features"
                                                                                                                                                                  :> ("limitedEventFanout"
                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Feature
                                                                                                                                                                               LimitedEventFanoutConfig)
                                                                                                                                                                          :> Put
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  LimitedEventFanoutConfig)))))))))))))
                                                                                                                           :<|> Named
                                                                                                                                  '("ipatch",
                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                  (Description
                                                                                                                                     ""
                                                                                                                                   :> (Summary
                                                                                                                                         "Patch config for limitedEventFanout"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('MissingPermission
                                                                                                                                                'Nothing)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("limitedEventFanout"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeaturePatch
                                                                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                                                               :> Patch
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        '("ilock", FileSharingConfig)
        (Summary "(Un-)lock fileSharing"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("fileSharing"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", ConferenceCallingConfig)
              (Summary "(Un-)lock conferenceCalling"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("conferenceCalling"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", SelfDeletingMessagesConfig)
                    (Summary "(Un-)lock selfDeletingMessages"
                     :> (Description ""
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("selfDeletingMessages"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("ilock", GuestLinksConfig)
                          (Summary "(Un-)lock conversationGuestLinks"
                           :> (Description ""
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("conversationGuestLinks"
                                                       :> (Capture "lockStatus" LockStatus
                                                           :> Put
                                                                '[JSON] LockStatusResponse)))))))))
                        :<|> (Named
                                '("ilock", SndFactorPasswordChallengeConfig)
                                (Summary "(Un-)lock sndFactorPasswordChallenge"
                                 :> (Description ""
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("sndFactorPasswordChallenge"
                                                             :> (Capture "lockStatus" LockStatus
                                                                 :> Put
                                                                      '[JSON]
                                                                      LockStatusResponse)))))))))
                              :<|> (Named
                                      '("ilock", MLSConfig)
                                      (Summary "(Un-)lock mls"
                                       :> (Description ""
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("mls"
                                                                   :> (Capture
                                                                         "lockStatus" LockStatus
                                                                       :> Put
                                                                            '[JSON]
                                                                            LockStatusResponse)))))))))
                                    :<|> (Named
                                            '("ilock", OutlookCalIntegrationConfig)
                                            (Summary "(Un-)lock outlookCalIntegration"
                                             :> (Description ""
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("outlookCalIntegration"
                                                                         :> (Capture
                                                                               "lockStatus"
                                                                               LockStatus
                                                                             :> Put
                                                                                  '[JSON]
                                                                                  LockStatusResponse)))))))))
                                          :<|> (Named
                                                  '("ilock", MlsE2EIdConfig)
                                                  (Summary "(Un-)lock mlsE2EId"
                                                   :> (Description ""
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("mlsE2EId"
                                                                               :> (Capture
                                                                                     "lockStatus"
                                                                                     LockStatus
                                                                                   :> Put
                                                                                        '[JSON]
                                                                                        LockStatusResponse)))))))))
                                                :<|> (Named
                                                        '("ilock", MlsMigrationConfig)
                                                        (Summary "(Un-)lock mlsMigration"
                                                         :> (Description ""
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("mlsMigration"
                                                                                     :> (Capture
                                                                                           "lockStatus"
                                                                                           LockStatus
                                                                                         :> Put
                                                                                              '[JSON]
                                                                                              LockStatusResponse)))))))))
                                                      :<|> (Named
                                                              '("ilock",
                                                                EnforceFileDownloadLocationConfig)
                                                              (Summary
                                                                 "(Un-)lock enforceFileDownloadLocation"
                                                               :> (Description
                                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("enforceFileDownloadLocation"
                                                                                           :> (Capture
                                                                                                 "lockStatus"
                                                                                                 LockStatus
                                                                                               :> Put
                                                                                                    '[JSON]
                                                                                                    LockStatusResponse)))))))))
                                                            :<|> (Named
                                                                    '("igetmulti",
                                                                      SearchVisibilityInboundConfig)
                                                                    (Summary
                                                                       "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                     :> ("features-multi-teams"
                                                                         :> ("searchVisibilityInbound"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   TeamFeatureNoConfigMultiRequest
                                                                                 :> Post
                                                                                      '[JSON]
                                                                                      (TeamFeatureNoConfigMultiResponse
                                                                                         SearchVisibilityInboundConfig)))))
                                                                  :<|> Named
                                                                         "feature-configs-internal"
                                                                         (Summary
                                                                            "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                          :> ("feature-configs"
                                                                              :> (CanThrow
                                                                                    ('MissingPermission
                                                                                       'Nothing)
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> (QueryParam'
                                                                                                '[Optional,
                                                                                                  Strict,
                                                                                                  Description
                                                                                                    "Optional user id"]
                                                                                                "user_id"
                                                                                                UserId
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   AllTeamFeatures)))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
          '("iget", LegalholdConfig)
          (Description ""
           :> (Summary "Get config for legalhold"
               :> (CanThrow ('MissingPermission 'Nothing)
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("legalhold"
                                           :> Get '[JSON] (LockableFeature LegalholdConfig))))))))))
        :<|> (Named
                '("iput", LegalholdConfig)
                (Description ""
                 :> (Summary "Put config for legalhold"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany
                                           '[ 'ActionDenied 'RemoveConversationMember,
                                              'CannotEnableLegalHoldServiceLargeTeam,
                                              'LegalHoldNotEnabled, 'LegalHoldDisableUnimplemented,
                                              'LegalHoldServiceNotRegistered,
                                              'UserLegalHoldIllegalOperation,
                                              'LegalHoldCouldNotBlockConnections]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("legalhold"
                                                         :> (ReqBody
                                                               '[JSON] (Feature LegalholdConfig)
                                                             :> Put
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     LegalholdConfig)))))))))))))
              :<|> Named
                     '("ipatch", LegalholdConfig)
                     (Description ""
                      :> (Summary "Patch config for legalhold"
                          :> (CanThrow ('MissingPermission 'Nothing)
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany
                                                '[ 'ActionDenied 'RemoveConversationMember,
                                                   'CannotEnableLegalHoldServiceLargeTeam,
                                                   'LegalHoldNotEnabled,
                                                   'LegalHoldDisableUnimplemented,
                                                   'LegalHoldServiceNotRegistered,
                                                   'UserLegalHoldIllegalOperation,
                                                   'LegalHoldCouldNotBlockConnections]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("legalhold"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (LockableFeaturePatch
                                                                       LegalholdConfig)
                                                                  :> Patch
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          LegalholdConfig)))))))))))))))
       :<|> ((Named
                '("iget", SSOConfig)
                (Description ""
                 :> (Summary "Get config for sso"
                     :> (CanThrow ('MissingPermission 'Nothing)
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("sso"
                                                 :> Get '[JSON] (LockableFeature SSOConfig))))))))))
              :<|> (Named
                      '("iput", SSOConfig)
                      (Description ""
                       :> (Summary "Put config for sso"
                           :> (CanThrow ('MissingPermission 'Nothing)
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany '[]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("sso"
                                                               :> (ReqBody
                                                                     '[JSON] (Feature SSOConfig)
                                                                   :> Put
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           SSOConfig)))))))))))))
                    :<|> Named
                           '("ipatch", SSOConfig)
                           (Description ""
                            :> (Summary "Patch config for sso"
                                :> (CanThrow ('MissingPermission 'Nothing)
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow 'TeamNotFound
                                            :> (CanThrow TeamFeatureError
                                                :> (CanThrowMany '[]
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("sso"
                                                                    :> (ReqBody
                                                                          '[JSON]
                                                                          (LockableFeaturePatch
                                                                             SSOConfig)
                                                                        :> Patch
                                                                             '[JSON]
                                                                             (LockableFeature
                                                                                SSOConfig)))))))))))))))
             :<|> ((Named
                      '("iget", SearchVisibilityAvailableConfig)
                      (Description ""
                       :> (Summary "Get config for searchVisibility"
                           :> (CanThrow ('MissingPermission 'Nothing)
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("searchVisibility"
                                                       :> Get
                                                            '[JSON]
                                                            (LockableFeature
                                                               SearchVisibilityAvailableConfig))))))))))
                    :<|> (Named
                            '("iput", SearchVisibilityAvailableConfig)
                            (Description ""
                             :> (Summary "Put config for searchVisibility"
                                 :> (CanThrow ('MissingPermission 'Nothing)
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow TeamFeatureError
                                                 :> (CanThrowMany '[]
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("searchVisibility"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           (Feature
                                                                              SearchVisibilityAvailableConfig)
                                                                         :> Put
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 SearchVisibilityAvailableConfig)))))))))))))
                          :<|> Named
                                 '("ipatch", SearchVisibilityAvailableConfig)
                                 (Description ""
                                  :> (Summary "Patch config for searchVisibility"
                                      :> (CanThrow ('MissingPermission 'Nothing)
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow TeamFeatureError
                                                      :> (CanThrowMany '[]
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("searchVisibility"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                (LockableFeaturePatch
                                                                                   SearchVisibilityAvailableConfig)
                                                                              :> Patch
                                                                                   '[JSON]
                                                                                   (LockableFeature
                                                                                      SearchVisibilityAvailableConfig)))))))))))))))
                   :<|> ((Named
                            '("iget", SearchVisibilityInboundConfig)
                            (Description ""
                             :> (Summary "Get config for searchVisibilityInbound"
                                 :> (CanThrow ('MissingPermission 'Nothing)
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("searchVisibilityInbound"
                                                             :> Get
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     SearchVisibilityInboundConfig))))))))))
                          :<|> (Named
                                  '("iput", SearchVisibilityInboundConfig)
                                  (Description ""
                                   :> (Summary "Put config for searchVisibilityInbound"
                                       :> (CanThrow ('MissingPermission 'Nothing)
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany '[]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("searchVisibilityInbound"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (Feature
                                                                                    SearchVisibilityInboundConfig)
                                                                               :> Put
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       SearchVisibilityInboundConfig)))))))))))))
                                :<|> Named
                                       '("ipatch", SearchVisibilityInboundConfig)
                                       (Description ""
                                        :> (Summary "Patch config for searchVisibilityInbound"
                                            :> (CanThrow ('MissingPermission 'Nothing)
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow 'TeamNotFound
                                                        :> (CanThrow TeamFeatureError
                                                            :> (CanThrowMany '[]
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("searchVisibilityInbound"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      (LockableFeaturePatch
                                                                                         SearchVisibilityInboundConfig)
                                                                                    :> Patch
                                                                                         '[JSON]
                                                                                         (LockableFeature
                                                                                            SearchVisibilityInboundConfig)))))))))))))))
                         :<|> ((Named
                                  '("iget", ValidateSAMLEmailsConfig)
                                  (Description ""
                                   :> (Summary "Get config for validateSAMLemails"
                                       :> (CanThrow ('MissingPermission 'Nothing)
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("validateSAMLemails"
                                                                   :> Get
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           ValidateSAMLEmailsConfig))))))))))
                                :<|> (Named
                                        '("iput", ValidateSAMLEmailsConfig)
                                        (Description ""
                                         :> (Summary "Put config for validateSAMLemails"
                                             :> (CanThrow ('MissingPermission 'Nothing)
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("validateSAMLemails"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (Feature
                                                                                          ValidateSAMLEmailsConfig)
                                                                                     :> Put
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             ValidateSAMLEmailsConfig)))))))))))))
                                      :<|> Named
                                             '("ipatch", ValidateSAMLEmailsConfig)
                                             (Description ""
                                              :> (Summary "Patch config for validateSAMLemails"
                                                  :> (CanThrow ('MissingPermission 'Nothing)
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow 'TeamNotFound
                                                              :> (CanThrow TeamFeatureError
                                                                  :> (CanThrowMany '[]
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("validateSAMLemails"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            (LockableFeaturePatch
                                                                                               ValidateSAMLEmailsConfig)
                                                                                          :> Patch
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  ValidateSAMLEmailsConfig)))))))))))))))
                               :<|> ((Named
                                        '("iget", DigitalSignaturesConfig)
                                        (Description ""
                                         :> (Summary "Get config for digitalSignatures"
                                             :> (CanThrow ('MissingPermission 'Nothing)
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("digitalSignatures"
                                                                         :> Get
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 DigitalSignaturesConfig))))))))))
                                      :<|> (Named
                                              '("iput", DigitalSignaturesConfig)
                                              (Description ""
                                               :> (Summary "Put config for digitalSignatures"
                                                   :> (CanThrow ('MissingPermission 'Nothing)
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("digitalSignatures"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (Feature
                                                                                                DigitalSignaturesConfig)
                                                                                           :> Put
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   DigitalSignaturesConfig)))))))))))))
                                            :<|> Named
                                                   '("ipatch", DigitalSignaturesConfig)
                                                   (Description ""
                                                    :> (Summary "Patch config for digitalSignatures"
                                                        :> (CanThrow ('MissingPermission 'Nothing)
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> (CanThrow TeamFeatureError
                                                                        :> (CanThrowMany '[]
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("digitalSignatures"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  (LockableFeaturePatch
                                                                                                     DigitalSignaturesConfig)
                                                                                                :> Patch
                                                                                                     '[JSON]
                                                                                                     (LockableFeature
                                                                                                        DigitalSignaturesConfig)))))))))))))))
                                     :<|> ((Named
                                              '("iget", AppLockConfig)
                                              (Description ""
                                               :> (Summary "Get config for appLock"
                                                   :> (CanThrow ('MissingPermission 'Nothing)
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("appLock"
                                                                               :> Get
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       AppLockConfig))))))))))
                                            :<|> (Named
                                                    '("iput", AppLockConfig)
                                                    (Description ""
                                                     :> (Summary "Put config for appLock"
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("appLock"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (Feature
                                                                                                      AppLockConfig)
                                                                                                 :> Put
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         AppLockConfig)))))))))))))
                                                  :<|> Named
                                                         '("ipatch", AppLockConfig)
                                                         (Description ""
                                                          :> (Summary "Patch config for appLock"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> (CanThrow
                                                                                TeamFeatureError
                                                                              :> (CanThrowMany '[]
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("appLock"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        (LockableFeaturePatch
                                                                                                           AppLockConfig)
                                                                                                      :> Patch
                                                                                                           '[JSON]
                                                                                                           (LockableFeature
                                                                                                              AppLockConfig)))))))))))))))
                                           :<|> ((Named
                                                    '("iget", FileSharingConfig)
                                                    (Description ""
                                                     :> (Summary "Get config for fileSharing"
                                                         :> (CanThrow ('MissingPermission 'Nothing)
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("fileSharing"
                                                                                     :> Get
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             FileSharingConfig))))))))))
                                                  :<|> (Named
                                                          '("iput", FileSharingConfig)
                                                          (Description ""
                                                           :> (Summary "Put config for fileSharing"
                                                               :> (CanThrow
                                                                     ('MissingPermission 'Nothing)
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("fileSharing"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (Feature
                                                                                                            FileSharingConfig)
                                                                                                       :> Put
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               FileSharingConfig)))))))))))))
                                                        :<|> Named
                                                               '("ipatch", FileSharingConfig)
                                                               (Description ""
                                                                :> (Summary
                                                                      "Patch config for fileSharing"
                                                                    :> (CanThrow
                                                                          ('MissingPermission
                                                                             'Nothing)
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> (CanThrow
                                                                                      TeamFeatureError
                                                                                    :> (CanThrowMany
                                                                                          '[]
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("fileSharing"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              (LockableFeaturePatch
                                                                                                                 FileSharingConfig)
                                                                                                            :> Patch
                                                                                                                 '[JSON]
                                                                                                                 (LockableFeature
                                                                                                                    FileSharingConfig)))))))))))))))
                                                 :<|> (Named
                                                         '("iget", ClassifiedDomainsConfig)
                                                         (Description ""
                                                          :> (Summary
                                                                "Get config for classifiedDomains"
                                                              :> (CanThrow
                                                                    ('MissingPermission 'Nothing)
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("classifiedDomains"
                                                                                          :> Get
                                                                                               '[JSON]
                                                                                               (LockableFeature
                                                                                                  ClassifiedDomainsConfig))))))))))
                                                       :<|> ((Named
                                                                '("iget", ConferenceCallingConfig)
                                                                (Description ""
                                                                 :> (Summary
                                                                       "Get config for conferenceCalling"
                                                                     :> (CanThrow
                                                                           ('MissingPermission
                                                                              'Nothing)
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("conferenceCalling"
                                                                                                 :> Get
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         ConferenceCallingConfig))))))))))
                                                              :<|> (Named
                                                                      '("iput",
                                                                        ConferenceCallingConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Put config for conferenceCalling"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("conferenceCalling"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (Feature
                                                                                                                        ConferenceCallingConfig)
                                                                                                                   :> Put
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           ConferenceCallingConfig)))))))))))))
                                                                    :<|> Named
                                                                           '("ipatch",
                                                                             ConferenceCallingConfig)
                                                                           (Description ""
                                                                            :> (Summary
                                                                                  "Patch config for conferenceCalling"
                                                                                :> (CanThrow
                                                                                      ('MissingPermission
                                                                                         'Nothing)
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> (CanThrow
                                                                                                  TeamFeatureError
                                                                                                :> (CanThrowMany
                                                                                                      '[]
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("conferenceCalling"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeaturePatch
                                                                                                                             ConferenceCallingConfig)
                                                                                                                        :> Patch
                                                                                                                             '[JSON]
                                                                                                                             (LockableFeature
                                                                                                                                ConferenceCallingConfig)))))))))))))))
                                                             :<|> ((Named
                                                                      '("iget",
                                                                        SelfDeletingMessagesConfig)
                                                                      (Description ""
                                                                       :> (Summary
                                                                             "Get config for selfDeletingMessages"
                                                                           :> (CanThrow
                                                                                 ('MissingPermission
                                                                                    'Nothing)
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("selfDeletingMessages"
                                                                                                       :> Get
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               SelfDeletingMessagesConfig))))))))))
                                                                    :<|> (Named
                                                                            '("iput",
                                                                              SelfDeletingMessagesConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Put config for selfDeletingMessages"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("selfDeletingMessages"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (Feature
                                                                                                                              SelfDeletingMessagesConfig)
                                                                                                                         :> Put
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 SelfDeletingMessagesConfig)))))))))))))
                                                                          :<|> Named
                                                                                 '("ipatch",
                                                                                   SelfDeletingMessagesConfig)
                                                                                 (Description ""
                                                                                  :> (Summary
                                                                                        "Patch config for selfDeletingMessages"
                                                                                      :> (CanThrow
                                                                                            ('MissingPermission
                                                                                               'Nothing)
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> (CanThrow
                                                                                                        TeamFeatureError
                                                                                                      :> (CanThrowMany
                                                                                                            '[]
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("selfDeletingMessages"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeaturePatch
                                                                                                                                   SelfDeletingMessagesConfig)
                                                                                                                              :> Patch
                                                                                                                                   '[JSON]
                                                                                                                                   (LockableFeature
                                                                                                                                      SelfDeletingMessagesConfig)))))))))))))))
                                                                   :<|> ((Named
                                                                            '("iget",
                                                                              GuestLinksConfig)
                                                                            (Description ""
                                                                             :> (Summary
                                                                                   "Get config for conversationGuestLinks"
                                                                                 :> (CanThrow
                                                                                       ('MissingPermission
                                                                                          'Nothing)
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("conversationGuestLinks"
                                                                                                             :> Get
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     GuestLinksConfig))))))))))
                                                                          :<|> (Named
                                                                                  '("iput",
                                                                                    GuestLinksConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Put config for conversationGuestLinks"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (Feature
                                                                                                                                    GuestLinksConfig)
                                                                                                                               :> Put
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       GuestLinksConfig)))))))))))))
                                                                                :<|> Named
                                                                                       '("ipatch",
                                                                                         GuestLinksConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (Summary
                                                                                              "Patch config for conversationGuestLinks"
                                                                                            :> (CanThrow
                                                                                                  ('MissingPermission
                                                                                                     'Nothing)
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> (CanThrow
                                                                                                              TeamFeatureError
                                                                                                            :> (CanThrowMany
                                                                                                                  '[]
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("conversationGuestLinks"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeaturePatch
                                                                                                                                         GuestLinksConfig)
                                                                                                                                    :> Patch
                                                                                                                                         '[JSON]
                                                                                                                                         (LockableFeature
                                                                                                                                            GuestLinksConfig)))))))))))))))
                                                                         :<|> ((Named
                                                                                  '("iget",
                                                                                    SndFactorPasswordChallengeConfig)
                                                                                  (Description ""
                                                                                   :> (Summary
                                                                                         "Get config for sndFactorPasswordChallenge"
                                                                                       :> (CanThrow
                                                                                             ('MissingPermission
                                                                                                'Nothing)
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("sndFactorPasswordChallenge"
                                                                                                                   :> Get
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           SndFactorPasswordChallengeConfig))))))))))
                                                                                :<|> (Named
                                                                                        '("iput",
                                                                                          SndFactorPasswordChallengeConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Put config for sndFactorPasswordChallenge"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("sndFactorPasswordChallenge"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (Feature
                                                                                                                                          SndFactorPasswordChallengeConfig)
                                                                                                                                     :> Put
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             SndFactorPasswordChallengeConfig)))))))))))))
                                                                                      :<|> Named
                                                                                             '("ipatch",
                                                                                               SndFactorPasswordChallengeConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (Summary
                                                                                                    "Patch config for sndFactorPasswordChallenge"
                                                                                                  :> (CanThrow
                                                                                                        ('MissingPermission
                                                                                                           'Nothing)
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> (CanThrow
                                                                                                                    TeamFeatureError
                                                                                                                  :> (CanThrowMany
                                                                                                                        '[]
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("sndFactorPasswordChallenge"
                                                                                                                                      :> (ReqBody
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeaturePatch
                                                                                                                                               SndFactorPasswordChallengeConfig)
                                                                                                                                          :> Patch
                                                                                                                                               '[JSON]
                                                                                                                                               (LockableFeature
                                                                                                                                                  SndFactorPasswordChallengeConfig)))))))))))))))
                                                                               :<|> ((Named
                                                                                        '("iget",
                                                                                          MLSConfig)
                                                                                        (Description
                                                                                           ""
                                                                                         :> (Summary
                                                                                               "Get config for mls"
                                                                                             :> (CanThrow
                                                                                                   ('MissingPermission
                                                                                                      'Nothing)
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("mls"
                                                                                                                         :> Get
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 MLSConfig))))))))))
                                                                                      :<|> (Named
                                                                                              '("iput",
                                                                                                MLSConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Put config for mls"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("mls"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (Feature
                                                                                                                                                MLSConfig)
                                                                                                                                           :> Put
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   MLSConfig)))))))))))))
                                                                                            :<|> Named
                                                                                                   '("ipatch",
                                                                                                     MLSConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (Summary
                                                                                                          "Patch config for mls"
                                                                                                        :> (CanThrow
                                                                                                              ('MissingPermission
                                                                                                                 'Nothing)
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> (CanThrow
                                                                                                                          TeamFeatureError
                                                                                                                        :> (CanThrowMany
                                                                                                                              '[]
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("mls"
                                                                                                                                            :> (ReqBody
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeaturePatch
                                                                                                                                                     MLSConfig)
                                                                                                                                                :> Patch
                                                                                                                                                     '[JSON]
                                                                                                                                                     (LockableFeature
                                                                                                                                                        MLSConfig)))))))))))))))
                                                                                     :<|> ((Named
                                                                                              '("iget",
                                                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                                                              (Description
                                                                                                 ""
                                                                                               :> (Summary
                                                                                                     "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                   :> (CanThrow
                                                                                                         ('MissingPermission
                                                                                                            'Nothing)
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                               :> Get
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                            :<|> (Named
                                                                                                    '("iput",
                                                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (Feature
                                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                 :> Put
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         ExposeInvitationURLsToTeamAdminConfig)))))))))))))
                                                                                                  :<|> Named
                                                                                                         '("ipatch",
                                                                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                                                                         (Description
                                                                                                            ""
                                                                                                          :> (Summary
                                                                                                                "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                              :> (CanThrow
                                                                                                                    ('MissingPermission
                                                                                                                       'Nothing)
                                                                                                                  :> (CanThrow
                                                                                                                        'NotATeamMember
                                                                                                                      :> (CanThrow
                                                                                                                            'TeamNotFound
                                                                                                                          :> (CanThrow
                                                                                                                                TeamFeatureError
                                                                                                                              :> (CanThrowMany
                                                                                                                                    '[]
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                  :> (ReqBody
                                                                                                                                                        '[JSON]
                                                                                                                                                        (LockableFeaturePatch
                                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                      :> Patch
                                                                                                                                                           '[JSON]
                                                                                                                                                           (LockableFeature
                                                                                                                                                              ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                           :<|> ((Named
                                                                                                    '("iget",
                                                                                                      OutlookCalIntegrationConfig)
                                                                                                    (Description
                                                                                                       ""
                                                                                                     :> (Summary
                                                                                                           "Get config for outlookCalIntegration"
                                                                                                         :> (CanThrow
                                                                                                               ('MissingPermission
                                                                                                                  'Nothing)
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("outlookCalIntegration"
                                                                                                                                     :> Get
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             OutlookCalIntegrationConfig))))))))))
                                                                                                  :<|> (Named
                                                                                                          '("iput",
                                                                                                            OutlookCalIntegrationConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Put config for outlookCalIntegration"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("outlookCalIntegration"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (Feature
                                                                                                                                                            OutlookCalIntegrationConfig)
                                                                                                                                                       :> Put
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               OutlookCalIntegrationConfig)))))))))))))
                                                                                                        :<|> Named
                                                                                                               '("ipatch",
                                                                                                                 OutlookCalIntegrationConfig)
                                                                                                               (Description
                                                                                                                  ""
                                                                                                                :> (Summary
                                                                                                                      "Patch config for outlookCalIntegration"
                                                                                                                    :> (CanThrow
                                                                                                                          ('MissingPermission
                                                                                                                             'Nothing)
                                                                                                                        :> (CanThrow
                                                                                                                              'NotATeamMember
                                                                                                                            :> (CanThrow
                                                                                                                                  'TeamNotFound
                                                                                                                                :> (CanThrow
                                                                                                                                      TeamFeatureError
                                                                                                                                    :> (CanThrowMany
                                                                                                                                          '[]
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("outlookCalIntegration"
                                                                                                                                                        :> (ReqBody
                                                                                                                                                              '[JSON]
                                                                                                                                                              (LockableFeaturePatch
                                                                                                                                                                 OutlookCalIntegrationConfig)
                                                                                                                                                            :> Patch
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 (LockableFeature
                                                                                                                                                                    OutlookCalIntegrationConfig)))))))))))))))
                                                                                                 :<|> ((Named
                                                                                                          '("iget",
                                                                                                            MlsE2EIdConfig)
                                                                                                          (Description
                                                                                                             ""
                                                                                                           :> (Summary
                                                                                                                 "Get config for mlsE2EId"
                                                                                                               :> (CanThrow
                                                                                                                     ('MissingPermission
                                                                                                                        'Nothing)
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("mlsE2EId"
                                                                                                                                           :> Get
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   MlsE2EIdConfig))))))))))
                                                                                                        :<|> (Named
                                                                                                                '("iput",
                                                                                                                  MlsE2EIdConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Put config for mlsE2EId"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("mlsE2EId"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (Feature
                                                                                                                                                                  MlsE2EIdConfig)
                                                                                                                                                             :> Put
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     MlsE2EIdConfig)))))))))))))
                                                                                                              :<|> Named
                                                                                                                     '("ipatch",
                                                                                                                       MlsE2EIdConfig)
                                                                                                                     (Description
                                                                                                                        ""
                                                                                                                      :> (Summary
                                                                                                                            "Patch config for mlsE2EId"
                                                                                                                          :> (CanThrow
                                                                                                                                ('MissingPermission
                                                                                                                                   'Nothing)
                                                                                                                              :> (CanThrow
                                                                                                                                    'NotATeamMember
                                                                                                                                  :> (CanThrow
                                                                                                                                        'TeamNotFound
                                                                                                                                      :> (CanThrow
                                                                                                                                            TeamFeatureError
                                                                                                                                          :> (CanThrowMany
                                                                                                                                                '[]
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("mlsE2EId"
                                                                                                                                                              :> (ReqBody
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (LockableFeaturePatch
                                                                                                                                                                       MlsE2EIdConfig)
                                                                                                                                                                  :> Patch
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       (LockableFeature
                                                                                                                                                                          MlsE2EIdConfig)))))))))))))))
                                                                                                       :<|> ((Named
                                                                                                                '("iget",
                                                                                                                  MlsMigrationConfig)
                                                                                                                (Description
                                                                                                                   ""
                                                                                                                 :> (Summary
                                                                                                                       "Get config for mlsMigration"
                                                                                                                     :> (CanThrow
                                                                                                                           ('MissingPermission
                                                                                                                              'Nothing)
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("mlsMigration"
                                                                                                                                                 :> Get
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         MlsMigrationConfig))))))))))
                                                                                                              :<|> (Named
                                                                                                                      '("iput",
                                                                                                                        MlsMigrationConfig)
                                                                                                                      (Description
                                                                                                                         ""
                                                                                                                       :> (Summary
                                                                                                                             "Put config for mlsMigration"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("mlsMigration"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (Feature
                                                                                                                                                                        MlsMigrationConfig)
                                                                                                                                                                   :> Put
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           MlsMigrationConfig)))))))))))))
                                                                                                                    :<|> Named
                                                                                                                           '("ipatch",
                                                                                                                             MlsMigrationConfig)
                                                                                                                           (Description
                                                                                                                              ""
                                                                                                                            :> (Summary
                                                                                                                                  "Patch config for mlsMigration"
                                                                                                                                :> (CanThrow
                                                                                                                                      ('MissingPermission
                                                                                                                                         'Nothing)
                                                                                                                                    :> (CanThrow
                                                                                                                                          'NotATeamMember
                                                                                                                                        :> (CanThrow
                                                                                                                                              'TeamNotFound
                                                                                                                                            :> (CanThrow
                                                                                                                                                  TeamFeatureError
                                                                                                                                                :> (CanThrowMany
                                                                                                                                                      '[]
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("mlsMigration"
                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          (LockableFeaturePatch
                                                                                                                                                                             MlsMigrationConfig)
                                                                                                                                                                        :> Patch
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                MlsMigrationConfig)))))))))))))))
                                                                                                             :<|> ((Named
                                                                                                                      '("iget",
                                                                                                                        EnforceFileDownloadLocationConfig)
                                                                                                                      (Description
                                                                                                                         "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                       :> (Summary
                                                                                                                             "Get config for enforceFileDownloadLocation"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('MissingPermission
                                                                                                                                    'Nothing)
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("enforceFileDownloadLocation"
                                                                                                                                                       :> Get
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               EnforceFileDownloadLocationConfig))))))))))
                                                                                                                    :<|> (Named
                                                                                                                            '("iput",
                                                                                                                              EnforceFileDownloadLocationConfig)
                                                                                                                            (Description
                                                                                                                               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                             :> (Summary
                                                                                                                                   "Put config for enforceFileDownloadLocation"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('MissingPermission
                                                                                                                                          'Nothing)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("enforceFileDownloadLocation"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (Feature
                                                                                                                                                                              EnforceFileDownloadLocationConfig)
                                                                                                                                                                         :> Put
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                          :<|> Named
                                                                                                                                 '("ipatch",
                                                                                                                                   EnforceFileDownloadLocationConfig)
                                                                                                                                 (Description
                                                                                                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                  :> (Summary
                                                                                                                                        "Patch config for enforceFileDownloadLocation"
                                                                                                                                      :> (CanThrow
                                                                                                                                            ('MissingPermission
                                                                                                                                               'Nothing)
                                                                                                                                          :> (CanThrow
                                                                                                                                                'NotATeamMember
                                                                                                                                              :> (CanThrow
                                                                                                                                                    'TeamNotFound
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        TeamFeatureError
                                                                                                                                                      :> (CanThrowMany
                                                                                                                                                            '[]
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("enforceFileDownloadLocation"
                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                (LockableFeaturePatch
                                                                                                                                                                                   EnforceFileDownloadLocationConfig)
                                                                                                                                                                              :> Patch
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                      EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                   :<|> (Named
                                                                                                                           '("iget",
                                                                                                                             LimitedEventFanoutConfig)
                                                                                                                           (Description
                                                                                                                              ""
                                                                                                                            :> (Summary
                                                                                                                                  "Get config for limitedEventFanout"
                                                                                                                                :> (CanThrow
                                                                                                                                      ('MissingPermission
                                                                                                                                         'Nothing)
                                                                                                                                    :> (CanThrow
                                                                                                                                          'NotATeamMember
                                                                                                                                        :> (CanThrow
                                                                                                                                              'TeamNotFound
                                                                                                                                            :> ("teams"
                                                                                                                                                :> (Capture
                                                                                                                                                      "tid"
                                                                                                                                                      TeamId
                                                                                                                                                    :> ("features"
                                                                                                                                                        :> ("limitedEventFanout"
                                                                                                                                                            :> Get
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 (LockableFeature
                                                                                                                                                                    LimitedEventFanoutConfig))))))))))
                                                                                                                         :<|> (Named
                                                                                                                                 '("iput",
                                                                                                                                   LimitedEventFanoutConfig)
                                                                                                                                 (Description
                                                                                                                                    ""
                                                                                                                                  :> (Summary
                                                                                                                                        "Put config for limitedEventFanout"
                                                                                                                                      :> (CanThrow
                                                                                                                                            ('MissingPermission
                                                                                                                                               'Nothing)
                                                                                                                                          :> (CanThrow
                                                                                                                                                'NotATeamMember
                                                                                                                                              :> (CanThrow
                                                                                                                                                    'TeamNotFound
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        TeamFeatureError
                                                                                                                                                      :> (CanThrowMany
                                                                                                                                                            '[]
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("limitedEventFanout"
                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                (Feature
                                                                                                                                                                                   LimitedEventFanoutConfig)
                                                                                                                                                                              :> Put
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                      LimitedEventFanoutConfig)))))))))))))
                                                                                                                               :<|> Named
                                                                                                                                      '("ipatch",
                                                                                                                                        LimitedEventFanoutConfig)
                                                                                                                                      (Description
                                                                                                                                         ""
                                                                                                                                       :> (Summary
                                                                                                                                             "Patch config for limitedEventFanout"
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('MissingPermission
                                                                                                                                                    'Nothing)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'NotATeamMember
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'TeamNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             TeamFeatureError
                                                                                                                                                           :> (CanThrowMany
                                                                                                                                                                 '[]
                                                                                                                                                               :> ("teams"
                                                                                                                                                                   :> (Capture
                                                                                                                                                                         "tid"
                                                                                                                                                                         TeamId
                                                                                                                                                                       :> ("features"
                                                                                                                                                                           :> ("limitedEventFanout"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeaturePatch
                                                                                                                                                                                        LimitedEventFanoutConfig)
                                                                                                                                                                                   :> Patch
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
      :<|> (Named
              '("ilock", FileSharingConfig)
              (Summary "(Un-)lock fileSharing"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("fileSharing"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", ConferenceCallingConfig)
                    (Summary "(Un-)lock conferenceCalling"
                     :> (Description ""
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("conferenceCalling"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("ilock", SelfDeletingMessagesConfig)
                          (Summary "(Un-)lock selfDeletingMessages"
                           :> (Description ""
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("selfDeletingMessages"
                                                       :> (Capture "lockStatus" LockStatus
                                                           :> Put
                                                                '[JSON] LockStatusResponse)))))))))
                        :<|> (Named
                                '("ilock", GuestLinksConfig)
                                (Summary "(Un-)lock conversationGuestLinks"
                                 :> (Description ""
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("conversationGuestLinks"
                                                             :> (Capture "lockStatus" LockStatus
                                                                 :> Put
                                                                      '[JSON]
                                                                      LockStatusResponse)))))))))
                              :<|> (Named
                                      '("ilock", SndFactorPasswordChallengeConfig)
                                      (Summary "(Un-)lock sndFactorPasswordChallenge"
                                       :> (Description ""
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("sndFactorPasswordChallenge"
                                                                   :> (Capture
                                                                         "lockStatus" LockStatus
                                                                       :> Put
                                                                            '[JSON]
                                                                            LockStatusResponse)))))))))
                                    :<|> (Named
                                            '("ilock", MLSConfig)
                                            (Summary "(Un-)lock mls"
                                             :> (Description ""
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("mls"
                                                                         :> (Capture
                                                                               "lockStatus"
                                                                               LockStatus
                                                                             :> Put
                                                                                  '[JSON]
                                                                                  LockStatusResponse)))))))))
                                          :<|> (Named
                                                  '("ilock", OutlookCalIntegrationConfig)
                                                  (Summary "(Un-)lock outlookCalIntegration"
                                                   :> (Description ""
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("outlookCalIntegration"
                                                                               :> (Capture
                                                                                     "lockStatus"
                                                                                     LockStatus
                                                                                   :> Put
                                                                                        '[JSON]
                                                                                        LockStatusResponse)))))))))
                                                :<|> (Named
                                                        '("ilock", MlsE2EIdConfig)
                                                        (Summary "(Un-)lock mlsE2EId"
                                                         :> (Description ""
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("mlsE2EId"
                                                                                     :> (Capture
                                                                                           "lockStatus"
                                                                                           LockStatus
                                                                                         :> Put
                                                                                              '[JSON]
                                                                                              LockStatusResponse)))))))))
                                                      :<|> (Named
                                                              '("ilock", MlsMigrationConfig)
                                                              (Summary "(Un-)lock mlsMigration"
                                                               :> (Description ""
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("mlsMigration"
                                                                                           :> (Capture
                                                                                                 "lockStatus"
                                                                                                 LockStatus
                                                                                               :> Put
                                                                                                    '[JSON]
                                                                                                    LockStatusResponse)))))))))
                                                            :<|> (Named
                                                                    '("ilock",
                                                                      EnforceFileDownloadLocationConfig)
                                                                    (Summary
                                                                       "(Un-)lock enforceFileDownloadLocation"
                                                                     :> (Description
                                                                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("enforceFileDownloadLocation"
                                                                                                 :> (Capture
                                                                                                       "lockStatus"
                                                                                                       LockStatus
                                                                                                     :> Put
                                                                                                          '[JSON]
                                                                                                          LockStatusResponse)))))))))
                                                                  :<|> (Named
                                                                          '("igetmulti",
                                                                            SearchVisibilityInboundConfig)
                                                                          (Summary
                                                                             "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                           :> ("features-multi-teams"
                                                                               :> ("searchVisibilityInbound"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         TeamFeatureNoConfigMultiRequest
                                                                                       :> Post
                                                                                            '[JSON]
                                                                                            (TeamFeatureNoConfigMultiResponse
                                                                                               SearchVisibilityInboundConfig)))))
                                                                        :<|> Named
                                                                               "feature-configs-internal"
                                                                               (Summary
                                                                                  "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                :> ("feature-configs"
                                                                                    :> (CanThrow
                                                                                          ('MissingPermission
                                                                                             'Nothing)
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> (QueryParam'
                                                                                                      '[Optional,
                                                                                                        Strict,
                                                                                                        Description
                                                                                                          "Optional user id"]
                                                                                                      "user_id"
                                                                                                      UserId
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         AllTeamFeatures))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @'("ilock", FileSharingConfig) (forall cfg (r :: EffectRow).
(IsFeatureConfig cfg, Member TeamFeatureStore r,
 Member TeamStore r, Member (Error (Tagged 'TeamNotFound ())) r) =>
TeamId -> LockStatus -> Sem r LockStatusResponse
updateLockStatus @FileSharingConfig)
    API
  (Named
     '("ilock", FileSharingConfig)
     (Summary "(Un-)lock fileSharing"
      :> (Description ""
          :> (CanThrow 'NotATeamMember
              :> (CanThrow 'TeamNotFound
                  :> ("teams"
                      :> (Capture "tid" TeamId
                          :> ("features"
                              :> ("fileSharing"
                                  :> (Capture "lockStatus" LockStatus
                                      :> Put '[JSON] LockStatusResponse))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        '("ilock", ConferenceCallingConfig)
        (Summary "(Un-)lock conferenceCalling"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("conferenceCalling"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", SelfDeletingMessagesConfig)
              (Summary "(Un-)lock selfDeletingMessages"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("selfDeletingMessages"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", GuestLinksConfig)
                    (Summary "(Un-)lock conversationGuestLinks"
                     :> (Description ""
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("conversationGuestLinks"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("ilock", SndFactorPasswordChallengeConfig)
                          (Summary "(Un-)lock sndFactorPasswordChallenge"
                           :> (Description ""
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("sndFactorPasswordChallenge"
                                                       :> (Capture "lockStatus" LockStatus
                                                           :> Put
                                                                '[JSON] LockStatusResponse)))))))))
                        :<|> (Named
                                '("ilock", MLSConfig)
                                (Summary "(Un-)lock mls"
                                 :> (Description ""
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("mls"
                                                             :> (Capture "lockStatus" LockStatus
                                                                 :> Put
                                                                      '[JSON]
                                                                      LockStatusResponse)))))))))
                              :<|> (Named
                                      '("ilock", OutlookCalIntegrationConfig)
                                      (Summary "(Un-)lock outlookCalIntegration"
                                       :> (Description ""
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("outlookCalIntegration"
                                                                   :> (Capture
                                                                         "lockStatus" LockStatus
                                                                       :> Put
                                                                            '[JSON]
                                                                            LockStatusResponse)))))))))
                                    :<|> (Named
                                            '("ilock", MlsE2EIdConfig)
                                            (Summary "(Un-)lock mlsE2EId"
                                             :> (Description ""
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("mlsE2EId"
                                                                         :> (Capture
                                                                               "lockStatus"
                                                                               LockStatus
                                                                             :> Put
                                                                                  '[JSON]
                                                                                  LockStatusResponse)))))))))
                                          :<|> (Named
                                                  '("ilock", MlsMigrationConfig)
                                                  (Summary "(Un-)lock mlsMigration"
                                                   :> (Description ""
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("mlsMigration"
                                                                               :> (Capture
                                                                                     "lockStatus"
                                                                                     LockStatus
                                                                                   :> Put
                                                                                        '[JSON]
                                                                                        LockStatusResponse)))))))))
                                                :<|> (Named
                                                        '("ilock",
                                                          EnforceFileDownloadLocationConfig)
                                                        (Summary
                                                           "(Un-)lock enforceFileDownloadLocation"
                                                         :> (Description
                                                               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("enforceFileDownloadLocation"
                                                                                     :> (Capture
                                                                                           "lockStatus"
                                                                                           LockStatus
                                                                                         :> Put
                                                                                              '[JSON]
                                                                                              LockStatusResponse)))))))))
                                                      :<|> (Named
                                                              '("igetmulti",
                                                                SearchVisibilityInboundConfig)
                                                              (Summary
                                                                 "Get team feature status in bulk for feature searchVisibilityInbound"
                                                               :> ("features-multi-teams"
                                                                   :> ("searchVisibilityInbound"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             TeamFeatureNoConfigMultiRequest
                                                                           :> Post
                                                                                '[JSON]
                                                                                (TeamFeatureNoConfigMultiResponse
                                                                                   SearchVisibilityInboundConfig)))))
                                                            :<|> Named
                                                                   "feature-configs-internal"
                                                                   (Summary
                                                                      "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                    :> ("feature-configs"
                                                                        :> (CanThrow
                                                                              ('MissingPermission
                                                                                 'Nothing)
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> (QueryParam'
                                                                                          '[Optional,
                                                                                            Strict,
                                                                                            Description
                                                                                              "Optional user id"]
                                                                                          "user_id"
                                                                                          UserId
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             AllTeamFeatures))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        '("ilock", FileSharingConfig)
        (Summary "(Un-)lock fileSharing"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("fileSharing"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", ConferenceCallingConfig)
              (Summary "(Un-)lock conferenceCalling"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("conferenceCalling"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", SelfDeletingMessagesConfig)
                    (Summary "(Un-)lock selfDeletingMessages"
                     :> (Description ""
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("selfDeletingMessages"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("ilock", GuestLinksConfig)
                          (Summary "(Un-)lock conversationGuestLinks"
                           :> (Description ""
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("conversationGuestLinks"
                                                       :> (Capture "lockStatus" LockStatus
                                                           :> Put
                                                                '[JSON] LockStatusResponse)))))))))
                        :<|> (Named
                                '("ilock", SndFactorPasswordChallengeConfig)
                                (Summary "(Un-)lock sndFactorPasswordChallenge"
                                 :> (Description ""
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("sndFactorPasswordChallenge"
                                                             :> (Capture "lockStatus" LockStatus
                                                                 :> Put
                                                                      '[JSON]
                                                                      LockStatusResponse)))))))))
                              :<|> (Named
                                      '("ilock", MLSConfig)
                                      (Summary "(Un-)lock mls"
                                       :> (Description ""
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("mls"
                                                                   :> (Capture
                                                                         "lockStatus" LockStatus
                                                                       :> Put
                                                                            '[JSON]
                                                                            LockStatusResponse)))))))))
                                    :<|> (Named
                                            '("ilock", OutlookCalIntegrationConfig)
                                            (Summary "(Un-)lock outlookCalIntegration"
                                             :> (Description ""
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("outlookCalIntegration"
                                                                         :> (Capture
                                                                               "lockStatus"
                                                                               LockStatus
                                                                             :> Put
                                                                                  '[JSON]
                                                                                  LockStatusResponse)))))))))
                                          :<|> (Named
                                                  '("ilock", MlsE2EIdConfig)
                                                  (Summary "(Un-)lock mlsE2EId"
                                                   :> (Description ""
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("mlsE2EId"
                                                                               :> (Capture
                                                                                     "lockStatus"
                                                                                     LockStatus
                                                                                   :> Put
                                                                                        '[JSON]
                                                                                        LockStatusResponse)))))))))
                                                :<|> (Named
                                                        '("ilock", MlsMigrationConfig)
                                                        (Summary "(Un-)lock mlsMigration"
                                                         :> (Description ""
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("mlsMigration"
                                                                                     :> (Capture
                                                                                           "lockStatus"
                                                                                           LockStatus
                                                                                         :> Put
                                                                                              '[JSON]
                                                                                              LockStatusResponse)))))))))
                                                      :<|> (Named
                                                              '("ilock",
                                                                EnforceFileDownloadLocationConfig)
                                                              (Summary
                                                                 "(Un-)lock enforceFileDownloadLocation"
                                                               :> (Description
                                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("enforceFileDownloadLocation"
                                                                                           :> (Capture
                                                                                                 "lockStatus"
                                                                                                 LockStatus
                                                                                               :> Put
                                                                                                    '[JSON]
                                                                                                    LockStatusResponse)))))))))
                                                            :<|> (Named
                                                                    '("igetmulti",
                                                                      SearchVisibilityInboundConfig)
                                                                    (Summary
                                                                       "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                     :> ("features-multi-teams"
                                                                         :> ("searchVisibilityInbound"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   TeamFeatureNoConfigMultiRequest
                                                                                 :> Post
                                                                                      '[JSON]
                                                                                      (TeamFeatureNoConfigMultiResponse
                                                                                         SearchVisibilityInboundConfig)))))
                                                                  :<|> Named
                                                                         "feature-configs-internal"
                                                                         (Summary
                                                                            "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                          :> ("feature-configs"
                                                                              :> (CanThrow
                                                                                    ('MissingPermission
                                                                                       'Nothing)
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> (QueryParam'
                                                                                                '[Optional,
                                                                                                  Strict,
                                                                                                  Description
                                                                                                    "Optional user id"]
                                                                                                "user_id"
                                                                                                UserId
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   AllTeamFeatures)))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @'("ilock", ConferenceCallingConfig) (forall cfg (r :: EffectRow).
(IsFeatureConfig cfg, Member TeamFeatureStore r,
 Member TeamStore r, Member (Error (Tagged 'TeamNotFound ())) r) =>
TeamId -> LockStatus -> Sem r LockStatusResponse
updateLockStatus @ConferenceCallingConfig)
    API
  (Named
     '("ilock", ConferenceCallingConfig)
     (Summary "(Un-)lock conferenceCalling"
      :> (Description ""
          :> (CanThrow 'NotATeamMember
              :> (CanThrow 'TeamNotFound
                  :> ("teams"
                      :> (Capture "tid" TeamId
                          :> ("features"
                              :> ("conferenceCalling"
                                  :> (Capture "lockStatus" LockStatus
                                      :> Put '[JSON] LockStatusResponse))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        '("ilock", SelfDeletingMessagesConfig)
        (Summary "(Un-)lock selfDeletingMessages"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("selfDeletingMessages"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", GuestLinksConfig)
              (Summary "(Un-)lock conversationGuestLinks"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("conversationGuestLinks"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", SndFactorPasswordChallengeConfig)
                    (Summary "(Un-)lock sndFactorPasswordChallenge"
                     :> (Description ""
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("sndFactorPasswordChallenge"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("ilock", MLSConfig)
                          (Summary "(Un-)lock mls"
                           :> (Description ""
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("mls"
                                                       :> (Capture "lockStatus" LockStatus
                                                           :> Put
                                                                '[JSON] LockStatusResponse)))))))))
                        :<|> (Named
                                '("ilock", OutlookCalIntegrationConfig)
                                (Summary "(Un-)lock outlookCalIntegration"
                                 :> (Description ""
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("outlookCalIntegration"
                                                             :> (Capture "lockStatus" LockStatus
                                                                 :> Put
                                                                      '[JSON]
                                                                      LockStatusResponse)))))))))
                              :<|> (Named
                                      '("ilock", MlsE2EIdConfig)
                                      (Summary "(Un-)lock mlsE2EId"
                                       :> (Description ""
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("mlsE2EId"
                                                                   :> (Capture
                                                                         "lockStatus" LockStatus
                                                                       :> Put
                                                                            '[JSON]
                                                                            LockStatusResponse)))))))))
                                    :<|> (Named
                                            '("ilock", MlsMigrationConfig)
                                            (Summary "(Un-)lock mlsMigration"
                                             :> (Description ""
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("mlsMigration"
                                                                         :> (Capture
                                                                               "lockStatus"
                                                                               LockStatus
                                                                             :> Put
                                                                                  '[JSON]
                                                                                  LockStatusResponse)))))))))
                                          :<|> (Named
                                                  '("ilock", EnforceFileDownloadLocationConfig)
                                                  (Summary "(Un-)lock enforceFileDownloadLocation"
                                                   :> (Description
                                                         "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("enforceFileDownloadLocation"
                                                                               :> (Capture
                                                                                     "lockStatus"
                                                                                     LockStatus
                                                                                   :> Put
                                                                                        '[JSON]
                                                                                        LockStatusResponse)))))))))
                                                :<|> (Named
                                                        '("igetmulti",
                                                          SearchVisibilityInboundConfig)
                                                        (Summary
                                                           "Get team feature status in bulk for feature searchVisibilityInbound"
                                                         :> ("features-multi-teams"
                                                             :> ("searchVisibilityInbound"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       TeamFeatureNoConfigMultiRequest
                                                                     :> Post
                                                                          '[JSON]
                                                                          (TeamFeatureNoConfigMultiResponse
                                                                             SearchVisibilityInboundConfig)))))
                                                      :<|> Named
                                                             "feature-configs-internal"
                                                             (Summary
                                                                "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                              :> ("feature-configs"
                                                                  :> (CanThrow
                                                                        ('MissingPermission
                                                                           'Nothing)
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> (QueryParam'
                                                                                    '[Optional,
                                                                                      Strict,
                                                                                      Description
                                                                                        "Optional user id"]
                                                                                    "user_id"
                                                                                    UserId
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       AllTeamFeatures)))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        '("ilock", ConferenceCallingConfig)
        (Summary "(Un-)lock conferenceCalling"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("conferenceCalling"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", SelfDeletingMessagesConfig)
              (Summary "(Un-)lock selfDeletingMessages"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("selfDeletingMessages"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", GuestLinksConfig)
                    (Summary "(Un-)lock conversationGuestLinks"
                     :> (Description ""
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("conversationGuestLinks"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("ilock", SndFactorPasswordChallengeConfig)
                          (Summary "(Un-)lock sndFactorPasswordChallenge"
                           :> (Description ""
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("sndFactorPasswordChallenge"
                                                       :> (Capture "lockStatus" LockStatus
                                                           :> Put
                                                                '[JSON] LockStatusResponse)))))))))
                        :<|> (Named
                                '("ilock", MLSConfig)
                                (Summary "(Un-)lock mls"
                                 :> (Description ""
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("mls"
                                                             :> (Capture "lockStatus" LockStatus
                                                                 :> Put
                                                                      '[JSON]
                                                                      LockStatusResponse)))))))))
                              :<|> (Named
                                      '("ilock", OutlookCalIntegrationConfig)
                                      (Summary "(Un-)lock outlookCalIntegration"
                                       :> (Description ""
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("outlookCalIntegration"
                                                                   :> (Capture
                                                                         "lockStatus" LockStatus
                                                                       :> Put
                                                                            '[JSON]
                                                                            LockStatusResponse)))))))))
                                    :<|> (Named
                                            '("ilock", MlsE2EIdConfig)
                                            (Summary "(Un-)lock mlsE2EId"
                                             :> (Description ""
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("mlsE2EId"
                                                                         :> (Capture
                                                                               "lockStatus"
                                                                               LockStatus
                                                                             :> Put
                                                                                  '[JSON]
                                                                                  LockStatusResponse)))))))))
                                          :<|> (Named
                                                  '("ilock", MlsMigrationConfig)
                                                  (Summary "(Un-)lock mlsMigration"
                                                   :> (Description ""
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("mlsMigration"
                                                                               :> (Capture
                                                                                     "lockStatus"
                                                                                     LockStatus
                                                                                   :> Put
                                                                                        '[JSON]
                                                                                        LockStatusResponse)))))))))
                                                :<|> (Named
                                                        '("ilock",
                                                          EnforceFileDownloadLocationConfig)
                                                        (Summary
                                                           "(Un-)lock enforceFileDownloadLocation"
                                                         :> (Description
                                                               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("enforceFileDownloadLocation"
                                                                                     :> (Capture
                                                                                           "lockStatus"
                                                                                           LockStatus
                                                                                         :> Put
                                                                                              '[JSON]
                                                                                              LockStatusResponse)))))))))
                                                      :<|> (Named
                                                              '("igetmulti",
                                                                SearchVisibilityInboundConfig)
                                                              (Summary
                                                                 "Get team feature status in bulk for feature searchVisibilityInbound"
                                                               :> ("features-multi-teams"
                                                                   :> ("searchVisibilityInbound"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             TeamFeatureNoConfigMultiRequest
                                                                           :> Post
                                                                                '[JSON]
                                                                                (TeamFeatureNoConfigMultiResponse
                                                                                   SearchVisibilityInboundConfig)))))
                                                            :<|> Named
                                                                   "feature-configs-internal"
                                                                   (Summary
                                                                      "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                    :> ("feature-configs"
                                                                        :> (CanThrow
                                                                              ('MissingPermission
                                                                                 'Nothing)
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> (QueryParam'
                                                                                          '[Optional,
                                                                                            Strict,
                                                                                            Description
                                                                                              "Optional user id"]
                                                                                          "user_id"
                                                                                          UserId
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             AllTeamFeatures))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @'("ilock", SelfDeletingMessagesConfig) (forall cfg (r :: EffectRow).
(IsFeatureConfig cfg, Member TeamFeatureStore r,
 Member TeamStore r, Member (Error (Tagged 'TeamNotFound ())) r) =>
TeamId -> LockStatus -> Sem r LockStatusResponse
updateLockStatus @SelfDeletingMessagesConfig)
    API
  (Named
     '("ilock", SelfDeletingMessagesConfig)
     (Summary "(Un-)lock selfDeletingMessages"
      :> (Description ""
          :> (CanThrow 'NotATeamMember
              :> (CanThrow 'TeamNotFound
                  :> ("teams"
                      :> (Capture "tid" TeamId
                          :> ("features"
                              :> ("selfDeletingMessages"
                                  :> (Capture "lockStatus" LockStatus
                                      :> Put '[JSON] LockStatusResponse))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        '("ilock", GuestLinksConfig)
        (Summary "(Un-)lock conversationGuestLinks"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("conversationGuestLinks"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", SndFactorPasswordChallengeConfig)
              (Summary "(Un-)lock sndFactorPasswordChallenge"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("sndFactorPasswordChallenge"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", MLSConfig)
                    (Summary "(Un-)lock mls"
                     :> (Description ""
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("mls"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("ilock", OutlookCalIntegrationConfig)
                          (Summary "(Un-)lock outlookCalIntegration"
                           :> (Description ""
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("outlookCalIntegration"
                                                       :> (Capture "lockStatus" LockStatus
                                                           :> Put
                                                                '[JSON] LockStatusResponse)))))))))
                        :<|> (Named
                                '("ilock", MlsE2EIdConfig)
                                (Summary "(Un-)lock mlsE2EId"
                                 :> (Description ""
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("mlsE2EId"
                                                             :> (Capture "lockStatus" LockStatus
                                                                 :> Put
                                                                      '[JSON]
                                                                      LockStatusResponse)))))))))
                              :<|> (Named
                                      '("ilock", MlsMigrationConfig)
                                      (Summary "(Un-)lock mlsMigration"
                                       :> (Description ""
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("mlsMigration"
                                                                   :> (Capture
                                                                         "lockStatus" LockStatus
                                                                       :> Put
                                                                            '[JSON]
                                                                            LockStatusResponse)))))))))
                                    :<|> (Named
                                            '("ilock", EnforceFileDownloadLocationConfig)
                                            (Summary "(Un-)lock enforceFileDownloadLocation"
                                             :> (Description
                                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("enforceFileDownloadLocation"
                                                                         :> (Capture
                                                                               "lockStatus"
                                                                               LockStatus
                                                                             :> Put
                                                                                  '[JSON]
                                                                                  LockStatusResponse)))))))))
                                          :<|> (Named
                                                  '("igetmulti", SearchVisibilityInboundConfig)
                                                  (Summary
                                                     "Get team feature status in bulk for feature searchVisibilityInbound"
                                                   :> ("features-multi-teams"
                                                       :> ("searchVisibilityInbound"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 TeamFeatureNoConfigMultiRequest
                                                               :> Post
                                                                    '[JSON]
                                                                    (TeamFeatureNoConfigMultiResponse
                                                                       SearchVisibilityInboundConfig)))))
                                                :<|> Named
                                                       "feature-configs-internal"
                                                       (Summary
                                                          "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                        :> ("feature-configs"
                                                            :> (CanThrow
                                                                  ('MissingPermission 'Nothing)
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> (QueryParam'
                                                                              '[Optional, Strict,
                                                                                Description
                                                                                  "Optional user id"]
                                                                              "user_id"
                                                                              UserId
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 AllTeamFeatures))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        '("ilock", SelfDeletingMessagesConfig)
        (Summary "(Un-)lock selfDeletingMessages"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("selfDeletingMessages"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", GuestLinksConfig)
              (Summary "(Un-)lock conversationGuestLinks"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("conversationGuestLinks"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", SndFactorPasswordChallengeConfig)
                    (Summary "(Un-)lock sndFactorPasswordChallenge"
                     :> (Description ""
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("sndFactorPasswordChallenge"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("ilock", MLSConfig)
                          (Summary "(Un-)lock mls"
                           :> (Description ""
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("mls"
                                                       :> (Capture "lockStatus" LockStatus
                                                           :> Put
                                                                '[JSON] LockStatusResponse)))))))))
                        :<|> (Named
                                '("ilock", OutlookCalIntegrationConfig)
                                (Summary "(Un-)lock outlookCalIntegration"
                                 :> (Description ""
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("outlookCalIntegration"
                                                             :> (Capture "lockStatus" LockStatus
                                                                 :> Put
                                                                      '[JSON]
                                                                      LockStatusResponse)))))))))
                              :<|> (Named
                                      '("ilock", MlsE2EIdConfig)
                                      (Summary "(Un-)lock mlsE2EId"
                                       :> (Description ""
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("mlsE2EId"
                                                                   :> (Capture
                                                                         "lockStatus" LockStatus
                                                                       :> Put
                                                                            '[JSON]
                                                                            LockStatusResponse)))))))))
                                    :<|> (Named
                                            '("ilock", MlsMigrationConfig)
                                            (Summary "(Un-)lock mlsMigration"
                                             :> (Description ""
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("mlsMigration"
                                                                         :> (Capture
                                                                               "lockStatus"
                                                                               LockStatus
                                                                             :> Put
                                                                                  '[JSON]
                                                                                  LockStatusResponse)))))))))
                                          :<|> (Named
                                                  '("ilock", EnforceFileDownloadLocationConfig)
                                                  (Summary "(Un-)lock enforceFileDownloadLocation"
                                                   :> (Description
                                                         "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("enforceFileDownloadLocation"
                                                                               :> (Capture
                                                                                     "lockStatus"
                                                                                     LockStatus
                                                                                   :> Put
                                                                                        '[JSON]
                                                                                        LockStatusResponse)))))))))
                                                :<|> (Named
                                                        '("igetmulti",
                                                          SearchVisibilityInboundConfig)
                                                        (Summary
                                                           "Get team feature status in bulk for feature searchVisibilityInbound"
                                                         :> ("features-multi-teams"
                                                             :> ("searchVisibilityInbound"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       TeamFeatureNoConfigMultiRequest
                                                                     :> Post
                                                                          '[JSON]
                                                                          (TeamFeatureNoConfigMultiResponse
                                                                             SearchVisibilityInboundConfig)))))
                                                      :<|> Named
                                                             "feature-configs-internal"
                                                             (Summary
                                                                "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                              :> ("feature-configs"
                                                                  :> (CanThrow
                                                                        ('MissingPermission
                                                                           'Nothing)
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> (QueryParam'
                                                                                    '[Optional,
                                                                                      Strict,
                                                                                      Description
                                                                                        "Optional user id"]
                                                                                    "user_id"
                                                                                    UserId
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       AllTeamFeatures)))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @'("ilock", GuestLinksConfig) (forall cfg (r :: EffectRow).
(IsFeatureConfig cfg, Member TeamFeatureStore r,
 Member TeamStore r, Member (Error (Tagged 'TeamNotFound ())) r) =>
TeamId -> LockStatus -> Sem r LockStatusResponse
updateLockStatus @GuestLinksConfig)
    API
  (Named
     '("ilock", GuestLinksConfig)
     (Summary "(Un-)lock conversationGuestLinks"
      :> (Description ""
          :> (CanThrow 'NotATeamMember
              :> (CanThrow 'TeamNotFound
                  :> ("teams"
                      :> (Capture "tid" TeamId
                          :> ("features"
                              :> ("conversationGuestLinks"
                                  :> (Capture "lockStatus" LockStatus
                                      :> Put '[JSON] LockStatusResponse))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        '("ilock", SndFactorPasswordChallengeConfig)
        (Summary "(Un-)lock sndFactorPasswordChallenge"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("sndFactorPasswordChallenge"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", MLSConfig)
              (Summary "(Un-)lock mls"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("mls"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", OutlookCalIntegrationConfig)
                    (Summary "(Un-)lock outlookCalIntegration"
                     :> (Description ""
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("outlookCalIntegration"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("ilock", MlsE2EIdConfig)
                          (Summary "(Un-)lock mlsE2EId"
                           :> (Description ""
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("mlsE2EId"
                                                       :> (Capture "lockStatus" LockStatus
                                                           :> Put
                                                                '[JSON] LockStatusResponse)))))))))
                        :<|> (Named
                                '("ilock", MlsMigrationConfig)
                                (Summary "(Un-)lock mlsMigration"
                                 :> (Description ""
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("mlsMigration"
                                                             :> (Capture "lockStatus" LockStatus
                                                                 :> Put
                                                                      '[JSON]
                                                                      LockStatusResponse)))))))))
                              :<|> (Named
                                      '("ilock", EnforceFileDownloadLocationConfig)
                                      (Summary "(Un-)lock enforceFileDownloadLocation"
                                       :> (Description
                                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("enforceFileDownloadLocation"
                                                                   :> (Capture
                                                                         "lockStatus" LockStatus
                                                                       :> Put
                                                                            '[JSON]
                                                                            LockStatusResponse)))))))))
                                    :<|> (Named
                                            '("igetmulti", SearchVisibilityInboundConfig)
                                            (Summary
                                               "Get team feature status in bulk for feature searchVisibilityInbound"
                                             :> ("features-multi-teams"
                                                 :> ("searchVisibilityInbound"
                                                     :> (ReqBody
                                                           '[JSON] TeamFeatureNoConfigMultiRequest
                                                         :> Post
                                                              '[JSON]
                                                              (TeamFeatureNoConfigMultiResponse
                                                                 SearchVisibilityInboundConfig)))))
                                          :<|> Named
                                                 "feature-configs-internal"
                                                 (Summary
                                                    "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                  :> ("feature-configs"
                                                      :> (CanThrow ('MissingPermission 'Nothing)
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> (QueryParam'
                                                                        '[Optional, Strict,
                                                                          Description
                                                                            "Optional user id"]
                                                                        "user_id"
                                                                        UserId
                                                                      :> Get
                                                                           '[JSON]
                                                                           AllTeamFeatures)))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        '("ilock", GuestLinksConfig)
        (Summary "(Un-)lock conversationGuestLinks"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("conversationGuestLinks"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", SndFactorPasswordChallengeConfig)
              (Summary "(Un-)lock sndFactorPasswordChallenge"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("sndFactorPasswordChallenge"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", MLSConfig)
                    (Summary "(Un-)lock mls"
                     :> (Description ""
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("mls"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("ilock", OutlookCalIntegrationConfig)
                          (Summary "(Un-)lock outlookCalIntegration"
                           :> (Description ""
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("outlookCalIntegration"
                                                       :> (Capture "lockStatus" LockStatus
                                                           :> Put
                                                                '[JSON] LockStatusResponse)))))))))
                        :<|> (Named
                                '("ilock", MlsE2EIdConfig)
                                (Summary "(Un-)lock mlsE2EId"
                                 :> (Description ""
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("mlsE2EId"
                                                             :> (Capture "lockStatus" LockStatus
                                                                 :> Put
                                                                      '[JSON]
                                                                      LockStatusResponse)))))))))
                              :<|> (Named
                                      '("ilock", MlsMigrationConfig)
                                      (Summary "(Un-)lock mlsMigration"
                                       :> (Description ""
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("mlsMigration"
                                                                   :> (Capture
                                                                         "lockStatus" LockStatus
                                                                       :> Put
                                                                            '[JSON]
                                                                            LockStatusResponse)))))))))
                                    :<|> (Named
                                            '("ilock", EnforceFileDownloadLocationConfig)
                                            (Summary "(Un-)lock enforceFileDownloadLocation"
                                             :> (Description
                                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("enforceFileDownloadLocation"
                                                                         :> (Capture
                                                                               "lockStatus"
                                                                               LockStatus
                                                                             :> Put
                                                                                  '[JSON]
                                                                                  LockStatusResponse)))))))))
                                          :<|> (Named
                                                  '("igetmulti", SearchVisibilityInboundConfig)
                                                  (Summary
                                                     "Get team feature status in bulk for feature searchVisibilityInbound"
                                                   :> ("features-multi-teams"
                                                       :> ("searchVisibilityInbound"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 TeamFeatureNoConfigMultiRequest
                                                               :> Post
                                                                    '[JSON]
                                                                    (TeamFeatureNoConfigMultiResponse
                                                                       SearchVisibilityInboundConfig)))))
                                                :<|> Named
                                                       "feature-configs-internal"
                                                       (Summary
                                                          "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                        :> ("feature-configs"
                                                            :> (CanThrow
                                                                  ('MissingPermission 'Nothing)
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> (QueryParam'
                                                                              '[Optional, Strict,
                                                                                Description
                                                                                  "Optional user id"]
                                                                              "user_id"
                                                                              UserId
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 AllTeamFeatures))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @'("ilock", SndFactorPasswordChallengeConfig) (forall cfg (r :: EffectRow).
(IsFeatureConfig cfg, Member TeamFeatureStore r,
 Member TeamStore r, Member (Error (Tagged 'TeamNotFound ())) r) =>
TeamId -> LockStatus -> Sem r LockStatusResponse
updateLockStatus @SndFactorPasswordChallengeConfig)
    API
  (Named
     '("ilock", SndFactorPasswordChallengeConfig)
     (Summary "(Un-)lock sndFactorPasswordChallenge"
      :> (Description ""
          :> (CanThrow 'NotATeamMember
              :> (CanThrow 'TeamNotFound
                  :> ("teams"
                      :> (Capture "tid" TeamId
                          :> ("features"
                              :> ("sndFactorPasswordChallenge"
                                  :> (Capture "lockStatus" LockStatus
                                      :> Put '[JSON] LockStatusResponse))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        '("ilock", MLSConfig)
        (Summary "(Un-)lock mls"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("mls"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", OutlookCalIntegrationConfig)
              (Summary "(Un-)lock outlookCalIntegration"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("outlookCalIntegration"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", MlsE2EIdConfig)
                    (Summary "(Un-)lock mlsE2EId"
                     :> (Description ""
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("mlsE2EId"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("ilock", MlsMigrationConfig)
                          (Summary "(Un-)lock mlsMigration"
                           :> (Description ""
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("mlsMigration"
                                                       :> (Capture "lockStatus" LockStatus
                                                           :> Put
                                                                '[JSON] LockStatusResponse)))))))))
                        :<|> (Named
                                '("ilock", EnforceFileDownloadLocationConfig)
                                (Summary "(Un-)lock enforceFileDownloadLocation"
                                 :> (Description
                                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("enforceFileDownloadLocation"
                                                             :> (Capture "lockStatus" LockStatus
                                                                 :> Put
                                                                      '[JSON]
                                                                      LockStatusResponse)))))))))
                              :<|> (Named
                                      '("igetmulti", SearchVisibilityInboundConfig)
                                      (Summary
                                         "Get team feature status in bulk for feature searchVisibilityInbound"
                                       :> ("features-multi-teams"
                                           :> ("searchVisibilityInbound"
                                               :> (ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
                                                   :> Post
                                                        '[JSON]
                                                        (TeamFeatureNoConfigMultiResponse
                                                           SearchVisibilityInboundConfig)))))
                                    :<|> Named
                                           "feature-configs-internal"
                                           (Summary
                                              "Get all feature configs (for user/team; if n/a fall back to site config)."
                                            :> ("feature-configs"
                                                :> (CanThrow ('MissingPermission 'Nothing)
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> (QueryParam'
                                                                  '[Optional, Strict,
                                                                    Description "Optional user id"]
                                                                  "user_id"
                                                                  UserId
                                                                :> Get
                                                                     '[JSON]
                                                                     AllTeamFeatures))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        '("ilock", SndFactorPasswordChallengeConfig)
        (Summary "(Un-)lock sndFactorPasswordChallenge"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("sndFactorPasswordChallenge"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", MLSConfig)
              (Summary "(Un-)lock mls"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("mls"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", OutlookCalIntegrationConfig)
                    (Summary "(Un-)lock outlookCalIntegration"
                     :> (Description ""
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("outlookCalIntegration"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("ilock", MlsE2EIdConfig)
                          (Summary "(Un-)lock mlsE2EId"
                           :> (Description ""
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("mlsE2EId"
                                                       :> (Capture "lockStatus" LockStatus
                                                           :> Put
                                                                '[JSON] LockStatusResponse)))))))))
                        :<|> (Named
                                '("ilock", MlsMigrationConfig)
                                (Summary "(Un-)lock mlsMigration"
                                 :> (Description ""
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("mlsMigration"
                                                             :> (Capture "lockStatus" LockStatus
                                                                 :> Put
                                                                      '[JSON]
                                                                      LockStatusResponse)))))))))
                              :<|> (Named
                                      '("ilock", EnforceFileDownloadLocationConfig)
                                      (Summary "(Un-)lock enforceFileDownloadLocation"
                                       :> (Description
                                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("enforceFileDownloadLocation"
                                                                   :> (Capture
                                                                         "lockStatus" LockStatus
                                                                       :> Put
                                                                            '[JSON]
                                                                            LockStatusResponse)))))))))
                                    :<|> (Named
                                            '("igetmulti", SearchVisibilityInboundConfig)
                                            (Summary
                                               "Get team feature status in bulk for feature searchVisibilityInbound"
                                             :> ("features-multi-teams"
                                                 :> ("searchVisibilityInbound"
                                                     :> (ReqBody
                                                           '[JSON] TeamFeatureNoConfigMultiRequest
                                                         :> Post
                                                              '[JSON]
                                                              (TeamFeatureNoConfigMultiResponse
                                                                 SearchVisibilityInboundConfig)))))
                                          :<|> Named
                                                 "feature-configs-internal"
                                                 (Summary
                                                    "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                  :> ("feature-configs"
                                                      :> (CanThrow ('MissingPermission 'Nothing)
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> (QueryParam'
                                                                        '[Optional, Strict,
                                                                          Description
                                                                            "Optional user id"]
                                                                        "user_id"
                                                                        UserId
                                                                      :> Get
                                                                           '[JSON]
                                                                           AllTeamFeatures)))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @'("ilock", MLSConfig) (forall cfg (r :: EffectRow).
(IsFeatureConfig cfg, Member TeamFeatureStore r,
 Member TeamStore r, Member (Error (Tagged 'TeamNotFound ())) r) =>
TeamId -> LockStatus -> Sem r LockStatusResponse
updateLockStatus @MLSConfig)
    API
  (Named
     '("ilock", MLSConfig)
     (Summary "(Un-)lock mls"
      :> (Description ""
          :> (CanThrow 'NotATeamMember
              :> (CanThrow 'TeamNotFound
                  :> ("teams"
                      :> (Capture "tid" TeamId
                          :> ("features"
                              :> ("mls"
                                  :> (Capture "lockStatus" LockStatus
                                      :> Put '[JSON] LockStatusResponse))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        '("ilock", OutlookCalIntegrationConfig)
        (Summary "(Un-)lock outlookCalIntegration"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("outlookCalIntegration"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", MlsE2EIdConfig)
              (Summary "(Un-)lock mlsE2EId"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("mlsE2EId"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", MlsMigrationConfig)
                    (Summary "(Un-)lock mlsMigration"
                     :> (Description ""
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("mlsMigration"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("ilock", EnforceFileDownloadLocationConfig)
                          (Summary "(Un-)lock enforceFileDownloadLocation"
                           :> (Description
                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("enforceFileDownloadLocation"
                                                       :> (Capture "lockStatus" LockStatus
                                                           :> Put
                                                                '[JSON] LockStatusResponse)))))))))
                        :<|> (Named
                                '("igetmulti", SearchVisibilityInboundConfig)
                                (Summary
                                   "Get team feature status in bulk for feature searchVisibilityInbound"
                                 :> ("features-multi-teams"
                                     :> ("searchVisibilityInbound"
                                         :> (ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
                                             :> Post
                                                  '[JSON]
                                                  (TeamFeatureNoConfigMultiResponse
                                                     SearchVisibilityInboundConfig)))))
                              :<|> Named
                                     "feature-configs-internal"
                                     (Summary
                                        "Get all feature configs (for user/team; if n/a fall back to site config)."
                                      :> ("feature-configs"
                                          :> (CanThrow ('MissingPermission 'Nothing)
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> (QueryParam'
                                                            '[Optional, Strict,
                                                              Description "Optional user id"]
                                                            "user_id"
                                                            UserId
                                                          :> Get '[JSON] AllTeamFeatures)))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        '("ilock", MLSConfig)
        (Summary "(Un-)lock mls"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("mls"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", OutlookCalIntegrationConfig)
              (Summary "(Un-)lock outlookCalIntegration"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("outlookCalIntegration"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", MlsE2EIdConfig)
                    (Summary "(Un-)lock mlsE2EId"
                     :> (Description ""
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("mlsE2EId"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("ilock", MlsMigrationConfig)
                          (Summary "(Un-)lock mlsMigration"
                           :> (Description ""
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("mlsMigration"
                                                       :> (Capture "lockStatus" LockStatus
                                                           :> Put
                                                                '[JSON] LockStatusResponse)))))))))
                        :<|> (Named
                                '("ilock", EnforceFileDownloadLocationConfig)
                                (Summary "(Un-)lock enforceFileDownloadLocation"
                                 :> (Description
                                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("enforceFileDownloadLocation"
                                                             :> (Capture "lockStatus" LockStatus
                                                                 :> Put
                                                                      '[JSON]
                                                                      LockStatusResponse)))))))))
                              :<|> (Named
                                      '("igetmulti", SearchVisibilityInboundConfig)
                                      (Summary
                                         "Get team feature status in bulk for feature searchVisibilityInbound"
                                       :> ("features-multi-teams"
                                           :> ("searchVisibilityInbound"
                                               :> (ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
                                                   :> Post
                                                        '[JSON]
                                                        (TeamFeatureNoConfigMultiResponse
                                                           SearchVisibilityInboundConfig)))))
                                    :<|> Named
                                           "feature-configs-internal"
                                           (Summary
                                              "Get all feature configs (for user/team; if n/a fall back to site config)."
                                            :> ("feature-configs"
                                                :> (CanThrow ('MissingPermission 'Nothing)
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> (QueryParam'
                                                                  '[Optional, Strict,
                                                                    Description "Optional user id"]
                                                                  "user_id"
                                                                  UserId
                                                                :> Get
                                                                     '[JSON]
                                                                     AllTeamFeatures))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @'("ilock", OutlookCalIntegrationConfig) (forall cfg (r :: EffectRow).
(IsFeatureConfig cfg, Member TeamFeatureStore r,
 Member TeamStore r, Member (Error (Tagged 'TeamNotFound ())) r) =>
TeamId -> LockStatus -> Sem r LockStatusResponse
updateLockStatus @OutlookCalIntegrationConfig)
    API
  (Named
     '("ilock", OutlookCalIntegrationConfig)
     (Summary "(Un-)lock outlookCalIntegration"
      :> (Description ""
          :> (CanThrow 'NotATeamMember
              :> (CanThrow 'TeamNotFound
                  :> ("teams"
                      :> (Capture "tid" TeamId
                          :> ("features"
                              :> ("outlookCalIntegration"
                                  :> (Capture "lockStatus" LockStatus
                                      :> Put '[JSON] LockStatusResponse))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        '("ilock", MlsE2EIdConfig)
        (Summary "(Un-)lock mlsE2EId"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("mlsE2EId"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", MlsMigrationConfig)
              (Summary "(Un-)lock mlsMigration"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("mlsMigration"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", EnforceFileDownloadLocationConfig)
                    (Summary "(Un-)lock enforceFileDownloadLocation"
                     :> (Description
                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("enforceFileDownloadLocation"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("igetmulti", SearchVisibilityInboundConfig)
                          (Summary
                             "Get team feature status in bulk for feature searchVisibilityInbound"
                           :> ("features-multi-teams"
                               :> ("searchVisibilityInbound"
                                   :> (ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
                                       :> Post
                                            '[JSON]
                                            (TeamFeatureNoConfigMultiResponse
                                               SearchVisibilityInboundConfig)))))
                        :<|> Named
                               "feature-configs-internal"
                               (Summary
                                  "Get all feature configs (for user/team; if n/a fall back to site config)."
                                :> ("feature-configs"
                                    :> (CanThrow ('MissingPermission 'Nothing)
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> (QueryParam'
                                                      '[Optional, Strict,
                                                        Description "Optional user id"]
                                                      "user_id"
                                                      UserId
                                                    :> Get '[JSON] AllTeamFeatures))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        '("ilock", OutlookCalIntegrationConfig)
        (Summary "(Un-)lock outlookCalIntegration"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("outlookCalIntegration"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", MlsE2EIdConfig)
              (Summary "(Un-)lock mlsE2EId"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("mlsE2EId"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", MlsMigrationConfig)
                    (Summary "(Un-)lock mlsMigration"
                     :> (Description ""
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("mlsMigration"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("ilock", EnforceFileDownloadLocationConfig)
                          (Summary "(Un-)lock enforceFileDownloadLocation"
                           :> (Description
                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("enforceFileDownloadLocation"
                                                       :> (Capture "lockStatus" LockStatus
                                                           :> Put
                                                                '[JSON] LockStatusResponse)))))))))
                        :<|> (Named
                                '("igetmulti", SearchVisibilityInboundConfig)
                                (Summary
                                   "Get team feature status in bulk for feature searchVisibilityInbound"
                                 :> ("features-multi-teams"
                                     :> ("searchVisibilityInbound"
                                         :> (ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
                                             :> Post
                                                  '[JSON]
                                                  (TeamFeatureNoConfigMultiResponse
                                                     SearchVisibilityInboundConfig)))))
                              :<|> Named
                                     "feature-configs-internal"
                                     (Summary
                                        "Get all feature configs (for user/team; if n/a fall back to site config)."
                                      :> ("feature-configs"
                                          :> (CanThrow ('MissingPermission 'Nothing)
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> (QueryParam'
                                                            '[Optional, Strict,
                                                              Description "Optional user id"]
                                                            "user_id"
                                                            UserId
                                                          :> Get '[JSON] AllTeamFeatures)))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @'("ilock", MlsE2EIdConfig) (forall cfg (r :: EffectRow).
(IsFeatureConfig cfg, Member TeamFeatureStore r,
 Member TeamStore r, Member (Error (Tagged 'TeamNotFound ())) r) =>
TeamId -> LockStatus -> Sem r LockStatusResponse
updateLockStatus @MlsE2EIdConfig)
    API
  (Named
     '("ilock", MlsE2EIdConfig)
     (Summary "(Un-)lock mlsE2EId"
      :> (Description ""
          :> (CanThrow 'NotATeamMember
              :> (CanThrow 'TeamNotFound
                  :> ("teams"
                      :> (Capture "tid" TeamId
                          :> ("features"
                              :> ("mlsE2EId"
                                  :> (Capture "lockStatus" LockStatus
                                      :> Put '[JSON] LockStatusResponse))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        '("ilock", MlsMigrationConfig)
        (Summary "(Un-)lock mlsMigration"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("mlsMigration"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", EnforceFileDownloadLocationConfig)
              (Summary "(Un-)lock enforceFileDownloadLocation"
               :> (Description
                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("enforceFileDownloadLocation"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("igetmulti", SearchVisibilityInboundConfig)
                    (Summary
                       "Get team feature status in bulk for feature searchVisibilityInbound"
                     :> ("features-multi-teams"
                         :> ("searchVisibilityInbound"
                             :> (ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
                                 :> Post
                                      '[JSON]
                                      (TeamFeatureNoConfigMultiResponse
                                         SearchVisibilityInboundConfig)))))
                  :<|> Named
                         "feature-configs-internal"
                         (Summary
                            "Get all feature configs (for user/team; if n/a fall back to site config)."
                          :> ("feature-configs"
                              :> (CanThrow ('MissingPermission 'Nothing)
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> (QueryParam'
                                                '[Optional, Strict, Description "Optional user id"]
                                                "user_id"
                                                UserId
                                              :> Get '[JSON] AllTeamFeatures)))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        '("ilock", MlsE2EIdConfig)
        (Summary "(Un-)lock mlsE2EId"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("mlsE2EId"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", MlsMigrationConfig)
              (Summary "(Un-)lock mlsMigration"
               :> (Description ""
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("mlsMigration"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("ilock", EnforceFileDownloadLocationConfig)
                    (Summary "(Un-)lock enforceFileDownloadLocation"
                     :> (Description
                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("enforceFileDownloadLocation"
                                                 :> (Capture "lockStatus" LockStatus
                                                     :> Put '[JSON] LockStatusResponse)))))))))
                  :<|> (Named
                          '("igetmulti", SearchVisibilityInboundConfig)
                          (Summary
                             "Get team feature status in bulk for feature searchVisibilityInbound"
                           :> ("features-multi-teams"
                               :> ("searchVisibilityInbound"
                                   :> (ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
                                       :> Post
                                            '[JSON]
                                            (TeamFeatureNoConfigMultiResponse
                                               SearchVisibilityInboundConfig)))))
                        :<|> Named
                               "feature-configs-internal"
                               (Summary
                                  "Get all feature configs (for user/team; if n/a fall back to site config)."
                                :> ("feature-configs"
                                    :> (CanThrow ('MissingPermission 'Nothing)
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> (QueryParam'
                                                      '[Optional, Strict,
                                                        Description "Optional user id"]
                                                      "user_id"
                                                      UserId
                                                    :> Get '[JSON] AllTeamFeatures))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @'("ilock", MlsMigrationConfig) (forall cfg (r :: EffectRow).
(IsFeatureConfig cfg, Member TeamFeatureStore r,
 Member TeamStore r, Member (Error (Tagged 'TeamNotFound ())) r) =>
TeamId -> LockStatus -> Sem r LockStatusResponse
updateLockStatus @MlsMigrationConfig)
    API
  (Named
     '("ilock", MlsMigrationConfig)
     (Summary "(Un-)lock mlsMigration"
      :> (Description ""
          :> (CanThrow 'NotATeamMember
              :> (CanThrow 'TeamNotFound
                  :> ("teams"
                      :> (Capture "tid" TeamId
                          :> ("features"
                              :> ("mlsMigration"
                                  :> (Capture "lockStatus" LockStatus
                                      :> Put '[JSON] LockStatusResponse))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        '("ilock", EnforceFileDownloadLocationConfig)
        (Summary "(Un-)lock enforceFileDownloadLocation"
         :> (Description
               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("enforceFileDownloadLocation"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("igetmulti", SearchVisibilityInboundConfig)
              (Summary
                 "Get team feature status in bulk for feature searchVisibilityInbound"
               :> ("features-multi-teams"
                   :> ("searchVisibilityInbound"
                       :> (ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
                           :> Post
                                '[JSON]
                                (TeamFeatureNoConfigMultiResponse
                                   SearchVisibilityInboundConfig)))))
            :<|> Named
                   "feature-configs-internal"
                   (Summary
                      "Get all feature configs (for user/team; if n/a fall back to site config)."
                    :> ("feature-configs"
                        :> (CanThrow ('MissingPermission 'Nothing)
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> (QueryParam'
                                          '[Optional, Strict, Description "Optional user id"]
                                          "user_id"
                                          UserId
                                        :> Get '[JSON] AllTeamFeatures))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        '("ilock", MlsMigrationConfig)
        (Summary "(Un-)lock mlsMigration"
         :> (Description ""
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("mlsMigration"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("ilock", EnforceFileDownloadLocationConfig)
              (Summary "(Un-)lock enforceFileDownloadLocation"
               :> (Description
                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("enforceFileDownloadLocation"
                                           :> (Capture "lockStatus" LockStatus
                                               :> Put '[JSON] LockStatusResponse)))))))))
            :<|> (Named
                    '("igetmulti", SearchVisibilityInboundConfig)
                    (Summary
                       "Get team feature status in bulk for feature searchVisibilityInbound"
                     :> ("features-multi-teams"
                         :> ("searchVisibilityInbound"
                             :> (ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
                                 :> Post
                                      '[JSON]
                                      (TeamFeatureNoConfigMultiResponse
                                         SearchVisibilityInboundConfig)))))
                  :<|> Named
                         "feature-configs-internal"
                         (Summary
                            "Get all feature configs (for user/team; if n/a fall back to site config)."
                          :> ("feature-configs"
                              :> (CanThrow ('MissingPermission 'Nothing)
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> (QueryParam'
                                                '[Optional, Strict, Description "Optional user id"]
                                                "user_id"
                                                UserId
                                              :> Get '[JSON] AllTeamFeatures)))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @'("ilock", EnforceFileDownloadLocationConfig) (forall cfg (r :: EffectRow).
(IsFeatureConfig cfg, Member TeamFeatureStore r,
 Member TeamStore r, Member (Error (Tagged 'TeamNotFound ())) r) =>
TeamId -> LockStatus -> Sem r LockStatusResponse
updateLockStatus @EnforceFileDownloadLocationConfig)
    -- special endpoints
    API
  (Named
     '("ilock", EnforceFileDownloadLocationConfig)
     (Summary "(Un-)lock enforceFileDownloadLocation"
      :> (Description
            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
          :> (CanThrow 'NotATeamMember
              :> (CanThrow 'TeamNotFound
                  :> ("teams"
                      :> (Capture "tid" TeamId
                          :> ("features"
                              :> ("enforceFileDownloadLocation"
                                  :> (Capture "lockStatus" LockStatus
                                      :> Put '[JSON] LockStatusResponse))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        '("igetmulti", SearchVisibilityInboundConfig)
        (Summary
           "Get team feature status in bulk for feature searchVisibilityInbound"
         :> ("features-multi-teams"
             :> ("searchVisibilityInbound"
                 :> (ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
                     :> Post
                          '[JSON]
                          (TeamFeatureNoConfigMultiResponse
                             SearchVisibilityInboundConfig)))))
      :<|> Named
             "feature-configs-internal"
             (Summary
                "Get all feature configs (for user/team; if n/a fall back to site config)."
              :> ("feature-configs"
                  :> (CanThrow ('MissingPermission 'Nothing)
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> (QueryParam'
                                    '[Optional, Strict, Description "Optional user id"]
                                    "user_id"
                                    UserId
                                  :> Get '[JSON] AllTeamFeatures)))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        '("ilock", EnforceFileDownloadLocationConfig)
        (Summary "(Un-)lock enforceFileDownloadLocation"
         :> (Description
               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow 'TeamNotFound
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("features"
                                 :> ("enforceFileDownloadLocation"
                                     :> (Capture "lockStatus" LockStatus
                                         :> Put '[JSON] LockStatusResponse)))))))))
      :<|> (Named
              '("igetmulti", SearchVisibilityInboundConfig)
              (Summary
                 "Get team feature status in bulk for feature searchVisibilityInbound"
               :> ("features-multi-teams"
                   :> ("searchVisibilityInbound"
                       :> (ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
                           :> Post
                                '[JSON]
                                (TeamFeatureNoConfigMultiResponse
                                   SearchVisibilityInboundConfig)))))
            :<|> Named
                   "feature-configs-internal"
                   (Summary
                      "Get all feature configs (for user/team; if n/a fall back to site config)."
                    :> ("feature-configs"
                        :> (CanThrow ('MissingPermission 'Nothing)
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> (QueryParam'
                                          '[Optional, Strict, Description "Optional user id"]
                                          "user_id"
                                          UserId
                                        :> Get '[JSON] AllTeamFeatures))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @'("igetmulti", SearchVisibilityInboundConfig) ServerT
  (Summary
     "Get team feature status in bulk for feature searchVisibilityInbound"
   :> ("features-multi-teams"
       :> ("searchVisibilityInbound"
           :> (ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
               :> Post
                    '[JSON]
                    (TeamFeatureNoConfigMultiResponse
                       SearchVisibilityInboundConfig)))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary
              "Get team feature status in bulk for feature searchVisibilityInbound"
            :> ("features-multi-teams"
                :> ("searchVisibilityInbound"
                    :> (ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
                        :> Post
                             '[JSON]
                             (TeamFeatureNoConfigMultiResponse
                                SearchVisibilityInboundConfig))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
TeamFeatureNoConfigMultiRequest
-> 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]
     (TeamFeatureNoConfigMultiResponse SearchVisibilityInboundConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 Member (Input Opts) r, Member TeamFeatureStore r) =>
TeamFeatureNoConfigMultiRequest
-> Sem r (TeamFeatureNoConfigMultiResponse cfg)
getFeatureMulti
    -- all features
    API
  (Named
     '("igetmulti", SearchVisibilityInboundConfig)
     (Summary
        "Get team feature status in bulk for feature searchVisibilityInbound"
      :> ("features-multi-teams"
          :> ("searchVisibilityInbound"
              :> (ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
                  :> Post
                       '[JSON]
                       (TeamFeatureNoConfigMultiResponse
                          SearchVisibilityInboundConfig))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "feature-configs-internal"
        (Summary
           "Get all feature configs (for user/team; if n/a fall back to site config)."
         :> ("feature-configs"
             :> (CanThrow ('MissingPermission 'Nothing)
                 :> (CanThrow 'NotATeamMember
                     :> (CanThrow 'TeamNotFound
                         :> (QueryParam'
                               '[Optional, Strict, Description "Optional user id"]
                               "user_id"
                               UserId
                             :> Get '[JSON] AllTeamFeatures)))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        '("igetmulti", SearchVisibilityInboundConfig)
        (Summary
           "Get team feature status in bulk for feature searchVisibilityInbound"
         :> ("features-multi-teams"
             :> ("searchVisibilityInbound"
                 :> (ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
                     :> Post
                          '[JSON]
                          (TeamFeatureNoConfigMultiResponse
                             SearchVisibilityInboundConfig)))))
      :<|> Named
             "feature-configs-internal"
             (Summary
                "Get all feature configs (for user/team; if n/a fall back to site config)."
              :> ("feature-configs"
                  :> (CanThrow ('MissingPermission 'Nothing)
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> (QueryParam'
                                    '[Optional, Strict, Description "Optional user id"]
                                    "user_id"
                                    UserId
                                  :> Get '[JSON] AllTeamFeatures)))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"feature-configs-internal" (Sem
  '[Error (Tagged ('MissingPermission 'Nothing) ()),
    Error (Tagged 'NotATeamMember ()), 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]
  AllTeamFeatures
-> (UserId
    -> Sem
         '[Error (Tagged ('MissingPermission 'Nothing) ()),
           Error (Tagged 'NotATeamMember ()), 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]
         AllTeamFeatures)
-> Maybe UserId
-> Sem
     '[Error (Tagged ('MissingPermission 'Nothing) ()),
       Error (Tagged 'NotATeamMember ()), 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]
     AllTeamFeatures
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Sem
  '[Error (Tagged ('MissingPermission 'Nothing) ()),
    Error (Tagged 'NotATeamMember ()), 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]
  AllTeamFeatures
forall (r :: EffectRow).
Member (Input Opts) r =>
Sem r AllTeamFeatures
getAllTeamFeaturesForServer UserId
-> Sem
     '[Error (Tagged ('MissingPermission 'Nothing) ()),
       Error (Tagged 'NotATeamMember ()), 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]
     AllTeamFeatures
forall (r :: EffectRow).
(Member BrigAccess r, Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r,
 Member (Error (Tagged ('MissingPermission 'Nothing) ())) r,
 Member (Input Opts) r, Member LegalHoldStore r,
 Member TeamFeatureStore r, Member TeamStore r) =>
UserId -> Sem r AllTeamFeatures
getAllTeamFeaturesForUser)

rmUser ::
  forall p1 p2 r.
  ( p1 ~ CassandraPaging,
    p2 ~ InternalPaging,
    Member BackendNotificationQueueAccess r,
    Member ClientStore r,
    Member ConversationStore r,
    Member (Error DynError) r,
    Member (Error FederationError) r,
    Member (Error InternalError) r,
    Member ExternalAccess r,
    Member NotificationSubsystem r,
    Member (Input Env) r,
    Member (Input Opts) r,
    Member (Input UTCTime) r,
    Member (ListItems p1 ConvId) r,
    Member (ListItems p1 (Remote ConvId)) r,
    Member (ListItems p2 TeamId) r,
    Member MemberStore r,
    Member ProposalStore r,
    Member P.TinyLog r,
    Member Random r,
    Member SubConversationStore r,
    Member TeamFeatureStore r,
    Member TeamStore r
  ) =>
  Local UserId ->
  Maybe ConnId ->
  Sem r ()
rmUser :: forall p1 p2 (r :: EffectRow).
(p1 ~ CassandraPaging, p2 ~ InternalPaging,
 Member BackendNotificationQueueAccess r, Member ClientStore r,
 Member ConversationStore r, Member (Error DynError) r,
 Member (Error FederationError) r, Member (Error InternalError) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input Env) r, Member (Input Opts) r,
 Member (Input UTCTime) r, Member (ListItems p1 ConvId) r,
 Member (ListItems p1 (Remote ConvId)) r,
 Member (ListItems p2 TeamId) r, Member MemberStore r,
 Member ProposalStore r, Member (Logger (Msg -> Msg)) r,
 Member Random r, Member SubConversationStore r,
 Member TeamFeatureStore r, Member TeamStore r) =>
QualifiedWithTag 'QLocal UserId -> Maybe ConnId -> Sem r ()
rmUser QualifiedWithTag 'QLocal UserId
lusr Maybe ConnId
conn = do
  let nRange1000 :: Range 1 1000 Int32
nRange1000 = Proxy 1000 -> Range 1 1000 Int32
forall (n :: Nat) (x :: Nat) (m :: Nat) a.
(n <= x, x <= m, KnownNat x, Num a) =>
Proxy x -> Range n m a
toRange (forall (t :: Nat). Proxy t
forall {k} (t :: k). Proxy t
Proxy @1000) :: Range 1 1000 Int32
  Page InternalPaging TeamId
tids <- UserId
-> Maybe (PagingState InternalPaging TeamId)
-> PagingBounds InternalPaging TeamId
-> Sem r (Page InternalPaging TeamId)
forall p (r :: EffectRow).
Member (ListItems p TeamId) r =>
UserId
-> Maybe (PagingState p TeamId)
-> PagingBounds p TeamId
-> Sem r (Page p TeamId)
listTeams (QualifiedWithTag 'QLocal UserId -> UserId
forall (t :: QTag) a. QualifiedWithTag t a -> a
tUnqualified QualifiedWithTag 'QLocal UserId
lusr) Maybe (PagingState InternalPaging TeamId)
Maybe (InternalPagingState TeamId)
forall a. Maybe a
Nothing PagingBounds InternalPaging TeamId
Range 1 100 Int32
forall a. Bounded a => a
maxBound
  Page InternalPaging TeamId -> Sem r ()
leaveTeams Page InternalPaging TeamId
tids
  ConvIdsPage
allConvIds <- QualifiedWithTag 'QLocal UserId
-> GetPaginatedConversationIds -> Sem r 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
Query.conversationIdsPageFrom QualifiedWithTag 'QLocal UserId
lusr (Maybe
  (MultiTablePagingState ConversationPagingName LocalOrRemoteTable)
-> Range 1 1000 Int32 -> GetPaginatedConversationIds
forall (name :: Symbol) tables (max :: Nat) (def :: Nat).
Maybe (MultiTablePagingState name tables)
-> Range 1 max Int32
-> GetMultiTablePageRequest name tables max def
GetPaginatedConversationIds Maybe
  (MultiTablePagingState ConversationPagingName LocalOrRemoteTable)
forall a. Maybe a
Nothing Range 1 1000 Int32
nRange1000)
  Range 1 1000 Int32 -> ConvIdsPage -> Sem r ()
goConvPages Range 1 1000 Int32
nRange1000 ConvIdsPage
allConvIds

  UserId -> Sem r ()
forall (r :: EffectRow). Member ClientStore r => UserId -> Sem r ()
deleteClients (QualifiedWithTag 'QLocal UserId -> UserId
forall (t :: QTag) a. QualifiedWithTag t a -> a
tUnqualified QualifiedWithTag 'QLocal UserId
lusr)
  where
    goConvPages :: Range 1 1000 Int32 -> ConvIdsPage -> Sem r ()
    goConvPages :: Range 1 1000 Int32 -> ConvIdsPage -> Sem r ()
goConvPages Range 1 1000 Int32
range ConvIdsPage
page = do
      let ([ConvId]
localConvs, [Remote ConvId]
remoteConvs) = QualifiedWithTag 'QLocal UserId
-> [Qualified ConvId] -> ([ConvId], [Remote ConvId])
forall (f :: * -> *) x a.
Foldable f =>
Local x -> f (Qualified a) -> ([a], [Remote a])
partitionQualified QualifiedWithTag 'QLocal UserId
lusr (ConvIdsPage -> [Qualified ConvId]
forall (name :: Symbol) (resultsKey :: Symbol) tables a.
MultiTablePage name resultsKey tables a -> [a]
mtpResults ConvIdsPage
page)
      [ConvId] -> Sem r ()
leaveLocalConversations [ConvId]
localConvs
      (Range 1 1000 [Remote ConvId] -> Sem r ())
-> [Range 1 1000 [Remote ConvId]] -> Sem r ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ Range 1 1000 [Remote ConvId] -> Sem r ()
leaveRemoteConversations ([Remote ConvId] -> [Range 1 1000 [Remote ConvId]]
forall a (n :: Nat).
(Within [a] 1 n, KnownNat n) =>
[a] -> [Range 1 n [a]]
rangedChunks [Remote ConvId]
remoteConvs)
      Bool -> Sem r () -> Sem r ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ConvIdsPage -> Bool
forall (name :: Symbol) (resultsKey :: Symbol) tables a.
MultiTablePage name resultsKey tables a -> Bool
mtpHasMore ConvIdsPage
page) (Sem r () -> Sem r ()) -> Sem r () -> Sem r ()
forall a b. (a -> b) -> a -> b
$ do
        let nextState :: MultiTablePagingState ConversationPagingName LocalOrRemoteTable
nextState = ConvIdsPage
-> MultiTablePagingState ConversationPagingName LocalOrRemoteTable
forall (name :: Symbol) (resultsKey :: Symbol) tables a.
MultiTablePage name resultsKey tables a
-> MultiTablePagingState name tables
mtpPagingState ConvIdsPage
page
            nextQuery :: GetPaginatedConversationIds
nextQuery = Maybe
  (MultiTablePagingState ConversationPagingName LocalOrRemoteTable)
-> Range 1 1000 Int32 -> GetPaginatedConversationIds
forall (name :: Symbol) tables (max :: Nat) (def :: Nat).
Maybe (MultiTablePagingState name tables)
-> Range 1 max Int32
-> GetMultiTablePageRequest name tables max def
GetPaginatedConversationIds (MultiTablePagingState ConversationPagingName LocalOrRemoteTable
-> Maybe
     (MultiTablePagingState ConversationPagingName LocalOrRemoteTable)
forall a. a -> Maybe a
Just MultiTablePagingState ConversationPagingName LocalOrRemoteTable
nextState) Range 1 1000 Int32
range
        ConvIdsPage
newCids <- QualifiedWithTag 'QLocal UserId
-> GetPaginatedConversationIds -> Sem r 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
Query.conversationIdsPageFrom QualifiedWithTag 'QLocal UserId
lusr GetPaginatedConversationIds
nextQuery
        Range 1 1000 Int32 -> ConvIdsPage -> Sem r ()
goConvPages Range 1 1000 Int32
range ConvIdsPage
newCids

    leaveTeams :: Page InternalPaging TeamId -> Sem r ()
leaveTeams Page InternalPaging TeamId
page = [TeamId] -> (TeamId -> Sem r ()) -> Sem r ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ (Page InternalPaging TeamId -> [TeamId]
forall p a. Paging p => Page p a -> [a]
forall a. Page InternalPaging a -> [a]
pageItems Page InternalPaging TeamId
page) ((TeamId -> Sem r ()) -> Sem r ())
-> (TeamId -> Sem r ()) -> Sem r ()
forall a b. (a -> b) -> a -> b
$ \TeamId
tid -> do
      Either [UserId] TeamMemberList
toNotify <-
        Sem
  (Error (Tagged 'NotATeamMember ())
     : Error (Tagged 'TeamNotFound ()) : r)
  (Either [UserId] TeamMemberList)
-> Sem r (Either [UserId] TeamMemberList)
forall a.
Sem
  (Error (Tagged 'NotATeamMember ())
     : Error (Tagged 'TeamNotFound ()) : r)
  a
-> Sem r a
handleImpossibleErrors (Sem
   (Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r)
   (Either [UserId] TeamMemberList)
 -> Sem r (Either [UserId] TeamMemberList))
-> Sem
     (Error (Tagged 'NotATeamMember ())
        : Error (Tagged 'TeamNotFound ()) : r)
     (Either [UserId] TeamMemberList)
-> Sem r (Either [UserId] TeamMemberList)
forall a b. (a -> b) -> a -> b
$
          forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 Member (Input Opts) r, Member TeamFeatureStore r) =>
TeamId -> Sem r (LockableFeature cfg)
getFeatureForTeam @LimitedEventFanoutConfig TeamId
tid
            Sem
  (Error (Tagged 'NotATeamMember ())
     : Error (Tagged 'TeamNotFound ()) : r)
  (LockableFeature LimitedEventFanoutConfig)
-> (LockableFeature LimitedEventFanoutConfig
    -> Sem
         (Error (Tagged 'NotATeamMember ())
            : Error (Tagged 'TeamNotFound ()) : r)
         (Either [UserId] TeamMemberList))
-> Sem
     (Error (Tagged 'NotATeamMember ())
        : Error (Tagged 'TeamNotFound ()) : r)
     (Either [UserId] TeamMemberList)
forall a b.
Sem
  (Error (Tagged 'NotATeamMember ())
     : Error (Tagged 'TeamNotFound ()) : r)
  a
-> (a
    -> Sem
         (Error (Tagged 'NotATeamMember ())
            : Error (Tagged 'TeamNotFound ()) : r)
         b)
-> Sem
     (Error (Tagged 'NotATeamMember ())
        : Error (Tagged 'TeamNotFound ()) : r)
     b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ( \case
                    FeatureStatus
FeatureStatusEnabled -> [UserId] -> Either [UserId] TeamMemberList
forall a b. a -> Either a b
Left ([UserId] -> Either [UserId] TeamMemberList)
-> Sem
     (Error (Tagged 'NotATeamMember ())
        : Error (Tagged 'TeamNotFound ()) : r)
     [UserId]
-> Sem
     (Error (Tagged 'NotATeamMember ())
        : Error (Tagged 'TeamNotFound ()) : r)
     (Either [UserId] TeamMemberList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TeamId
-> Sem
     (Error (Tagged 'NotATeamMember ())
        : Error (Tagged 'TeamNotFound ()) : r)
     [UserId]
forall (r :: EffectRow).
Member TeamStore r =>
TeamId -> Sem r [UserId]
E.getTeamAdmins TeamId
tid
                    FeatureStatus
FeatureStatusDisabled -> TeamMemberList -> Either [UserId] TeamMemberList
forall a b. b -> Either a b
Right (TeamMemberList -> Either [UserId] TeamMemberList)
-> Sem
     (Error (Tagged 'NotATeamMember ())
        : Error (Tagged 'TeamNotFound ()) : r)
     TeamMemberList
-> Sem
     (Error (Tagged 'NotATeamMember ())
        : Error (Tagged 'TeamNotFound ()) : r)
     (Either [UserId] TeamMemberList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TeamId
-> Sem
     (Error (Tagged 'NotATeamMember ())
        : Error (Tagged 'TeamNotFound ()) : r)
     TeamMemberList
forall (r :: EffectRow).
Member TeamStore r =>
TeamId -> Sem r TeamMemberList
getTeamMembersForFanout TeamId
tid
                )
              (FeatureStatus
 -> Sem
      (Error (Tagged 'NotATeamMember ())
         : Error (Tagged 'TeamNotFound ()) : r)
      (Either [UserId] TeamMemberList))
-> (LockableFeature LimitedEventFanoutConfig -> FeatureStatus)
-> LockableFeature LimitedEventFanoutConfig
-> Sem
     (Error (Tagged 'NotATeamMember ())
        : Error (Tagged 'TeamNotFound ()) : r)
     (Either [UserId] TeamMemberList)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (.status)
      QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> TeamId
-> UserId
-> Either [UserId] TeamMemberList
-> Sem r ()
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r,
 Member ConversationStore r, Member NotificationSubsystem r,
 Member (Error FederationError) r, Member ExternalAccess r,
 Member (Input UTCTime) r, Member MemberStore r,
 Member TeamStore r) =>
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> TeamId
-> UserId
-> Either [UserId] TeamMemberList
-> Sem r ()
uncheckedDeleteTeamMember QualifiedWithTag 'QLocal UserId
lusr Maybe ConnId
conn TeamId
tid (QualifiedWithTag 'QLocal UserId -> UserId
forall (t :: QTag) a. QualifiedWithTag t a -> a
tUnqualified QualifiedWithTag 'QLocal UserId
lusr) Either [UserId] TeamMemberList
toNotify
      Page InternalPaging TeamId
page' <- forall p (r :: EffectRow).
Member (ListItems p TeamId) r =>
UserId
-> Maybe (PagingState p TeamId)
-> PagingBounds p TeamId
-> Sem r (Page p TeamId)
listTeams @p2 (QualifiedWithTag 'QLocal UserId -> UserId
forall (t :: QTag) a. QualifiedWithTag t a -> a
tUnqualified QualifiedWithTag 'QLocal UserId
lusr) (InternalPagingState TeamId -> Maybe (InternalPagingState TeamId)
forall a. a -> Maybe a
Just (Page InternalPaging TeamId -> PagingState InternalPaging TeamId
forall p a. Paging p => Page p a -> PagingState p a
forall a. Page InternalPaging a -> PagingState InternalPaging a
pageState Page InternalPaging TeamId
page)) PagingBounds p2 TeamId
Range 1 100 Int32
forall a. Bounded a => a
maxBound
      Page InternalPaging TeamId -> Sem r ()
leaveTeams Page InternalPaging TeamId
page'

    -- The @'NotATeamMember@ and @'TeamNotFound@ errors cannot happen at this
    -- point: the user is a team member because we fetched the list of teams
    -- they are member of, and conversely the list of teams was fetched exactly
    -- for this user so it cannot be that the team is not found. Therefore, this
    -- helper just drops the errors.
    handleImpossibleErrors ::
      Sem
        ( ErrorS 'NotATeamMember
            ': ErrorS 'TeamNotFound
            ': r
        )
        a ->
      Sem r a
    handleImpossibleErrors :: forall a.
Sem
  (Error (Tagged 'NotATeamMember ())
     : Error (Tagged 'TeamNotFound ()) : r)
  a
-> Sem r a
handleImpossibleErrors Sem
  (Error (Tagged 'NotATeamMember ())
     : Error (Tagged 'TeamNotFound ()) : r)
  a
action =
      forall {k} (e :: k) (r :: EffectRow) a.
(Member (Error DynError) r, KnownError (MapError e)) =>
Sem (ErrorS e : r) a -> Sem r a
forall (e :: GalleyError) (r :: EffectRow) a.
(Member (Error DynError) r, KnownError (MapError e)) =>
Sem (ErrorS e : r) a -> Sem r a
mapToDynamicError @'TeamNotFound (forall {k} (e :: k) (r :: EffectRow) a.
(Member (Error DynError) r, KnownError (MapError e)) =>
Sem (ErrorS e : r) a -> Sem r a
forall (e :: GalleyError) (r :: EffectRow) a.
(Member (Error DynError) r, KnownError (MapError e)) =>
Sem (ErrorS e : r) a -> Sem r a
mapToDynamicError @'NotATeamMember Sem
  (Error (Tagged 'NotATeamMember ())
     : Error (Tagged 'TeamNotFound ()) : r)
  a
action)

    leaveLocalConversations :: [ConvId] -> Sem r ()
    leaveLocalConversations :: [ConvId] -> Sem r ()
leaveLocalConversations [ConvId]
ids = do
      let qUser :: Qualified UserId
qUser = QualifiedWithTag 'QLocal UserId -> Qualified UserId
forall (t :: QTag) a. QualifiedWithTag t a -> Qualified a
tUntagged QualifiedWithTag 'QLocal UserId
lusr
      [Conversation]
cc <- [ConvId] -> Sem r [Conversation]
forall (r :: EffectRow).
Member ConversationStore r =>
[ConvId] -> Sem r [Conversation]
getConversations [ConvId]
ids
      UTCTime
now <- Sem r UTCTime
forall i (r :: EffectRow). Member (Input i) r => Sem r i
input
      [Maybe Push]
pp <- [Conversation]
-> (Conversation -> Sem r (Maybe Push)) -> Sem r [Maybe Push]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [Conversation]
cc ((Conversation -> Sem r (Maybe Push)) -> Sem r [Maybe Push])
-> (Conversation -> Sem r (Maybe Push)) -> Sem r [Maybe Push]
forall a b. (a -> b) -> a -> b
$ \Conversation
c -> case Conversation -> ConvType
Data.convType Conversation
c of
        ConvType
SelfConv -> Maybe Push -> Sem r (Maybe Push)
forall a. a -> Sem r a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Push
forall a. Maybe a
Nothing
        ConvType
One2OneConv -> ConvId -> UserList UserId -> Sem r ()
forall (r :: EffectRow).
Member MemberStore r =>
ConvId -> UserList UserId -> Sem r ()
E.deleteMembers (Conversation -> ConvId
Data.convId Conversation
c) ([UserId] -> [Remote UserId] -> UserList UserId
forall a. [a] -> [Remote a] -> UserList a
UserList [QualifiedWithTag 'QLocal UserId -> UserId
forall (t :: QTag) a. QualifiedWithTag t a -> a
tUnqualified QualifiedWithTag 'QLocal UserId
lusr] []) Sem r () -> Maybe Push -> Sem r (Maybe Push)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Push
forall a. Maybe a
Nothing
        ConvType
ConnectConv -> ConvId -> UserList UserId -> Sem r ()
forall (r :: EffectRow).
Member MemberStore r =>
ConvId -> UserList UserId -> Sem r ()
E.deleteMembers (Conversation -> ConvId
Data.convId Conversation
c) ([UserId] -> [Remote UserId] -> UserList UserId
forall a. [a] -> [Remote a] -> UserList a
UserList [QualifiedWithTag 'QLocal UserId -> UserId
forall (t :: QTag) a. QualifiedWithTag t a -> a
tUnqualified QualifiedWithTag 'QLocal UserId
lusr] []) Sem r () -> Maybe Push -> Sem r (Maybe Push)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Push
forall a. Maybe a
Nothing
        ConvType
RegularConv
          | QualifiedWithTag 'QLocal UserId -> UserId
forall (t :: QTag) a. QualifiedWithTag t a -> a
tUnqualified QualifiedWithTag 'QLocal UserId
lusr UserId -> [LocalMember] -> Bool
forall (m :: * -> *). Foldable m => UserId -> m LocalMember -> Bool
`isMember` Conversation -> [LocalMember]
Data.convLocalMembers Conversation
c -> do
              Sem (Error InternalError : r) () -> Sem r (Either InternalError ())
forall e (r :: EffectRow) a.
Sem (Error e : r) a -> Sem r (Either e a)
runError (Local Conversation
-> RemoveUserIncludeMain
-> Qualified UserId
-> Sem (Error InternalError : r) ()
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r,
 Member (Error FederationError) r, Member ExternalAccess 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) =>
Local Conversation
-> RemoveUserIncludeMain -> Qualified UserId -> Sem r ()
removeUser (QualifiedWithTag 'QLocal UserId
-> Conversation -> Local Conversation
forall (t :: QTag) x a.
QualifiedWithTag t x -> a -> QualifiedWithTag t a
qualifyAs QualifiedWithTag 'QLocal UserId
lusr Conversation
c) RemoveUserIncludeMain
RemoveUserIncludeMain (QualifiedWithTag 'QLocal UserId -> Qualified UserId
forall (t :: QTag) a. QualifiedWithTag t a -> Qualified a
tUntagged QualifiedWithTag 'QLocal UserId
lusr)) Sem r (Either InternalError ())
-> (Either InternalError () -> Sem r ()) -> Sem r ()
forall a b. Sem r a -> (a -> Sem r b) -> Sem r b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
                Left InternalError
e -> (Msg -> Msg) -> Sem r ()
forall msg (r :: EffectRow).
Member (Logger msg) r =>
msg -> Sem r ()
P.err ((Msg -> Msg) -> Sem r ()) -> (Msg -> Msg) -> Sem r ()
forall a b. (a -> b) -> a -> b
$ LText -> Msg -> Msg
forall a. ToBytes a => a -> Msg -> Msg
Log.msg (LText
"failed to send remove proposal: " LText -> LText -> LText
forall a. Semigroup a => a -> a -> a
<> InternalError -> LText
internalErrorDescription InternalError
e)
                Right ()
_ -> () -> Sem r ()
forall a. a -> Sem r a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
              ConvId -> UserList UserId -> Sem r ()
forall (r :: EffectRow).
Member MemberStore r =>
ConvId -> UserList UserId -> Sem r ()
E.deleteMembers (Conversation -> ConvId
Data.convId Conversation
c) ([UserId] -> [Remote UserId] -> UserList UserId
forall a. [a] -> [Remote a] -> UserList a
UserList [QualifiedWithTag 'QLocal UserId -> UserId
forall (t :: QTag) a. QualifiedWithTag t a -> a
tUnqualified QualifiedWithTag 'QLocal UserId
lusr] [])
              let e :: Event
e =
                    Qualified ConvId
-> Maybe SubConvId
-> Qualified UserId
-> UTCTime
-> EventData
-> Event
Event
                      (QualifiedWithTag 'QLocal ConvId -> Qualified ConvId
forall (t :: QTag) a. QualifiedWithTag t a -> Qualified a
tUntagged (QualifiedWithTag 'QLocal UserId
-> ConvId -> QualifiedWithTag 'QLocal ConvId
forall (t :: QTag) x a.
QualifiedWithTag t x -> a -> QualifiedWithTag t a
qualifyAs QualifiedWithTag 'QLocal UserId
lusr (Conversation -> ConvId
Data.convId Conversation
c)))
                      Maybe SubConvId
forall a. Maybe a
Nothing
                      (QualifiedWithTag 'QLocal UserId -> Qualified UserId
forall (t :: QTag) a. QualifiedWithTag t a -> Qualified a
tUntagged QualifiedWithTag 'QLocal UserId
lusr)
                      UTCTime
now
                      (EdMemberLeftReason -> QualifiedUserIdList -> EventData
EdMembersLeave EdMemberLeftReason
EdReasonDeleted ([Qualified UserId] -> QualifiedUserIdList
QualifiedUserIdList [Qualified UserId
qUser]))
              [Remote [UserId]] -> (Remote [UserId] -> Sem r ()) -> Sem r ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ ([Remote UserId] -> [Remote [UserId]]
forall (f :: * -> *) a.
(Functor f, Foldable f) =>
f (Remote a) -> [Remote [a]]
bucketRemote ((RemoteMember -> Remote UserId)
-> [RemoteMember] -> [Remote UserId]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap RemoteMember -> Remote UserId
rmId (Conversation -> [RemoteMember]
Data.convRemoteMembers Conversation
c))) ((Remote [UserId] -> Sem r ()) -> Sem r ())
-> (Remote [UserId] -> Sem r ()) -> Sem r ()
forall a b. (a -> b) -> a -> b
$ UTCTime
-> Qualified UserId -> ConvId -> Remote [UserId] -> Sem r ()
notifyRemoteMembers UTCTime
now Qualified UserId
qUser (Conversation -> ConvId
Data.convId Conversation
c)
              Maybe Push -> Sem r (Maybe Push)
forall a. a -> Sem r a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Push -> Sem r (Maybe Push))
-> Maybe Push -> Sem r (Maybe Push)
forall a b. (a -> b) -> a -> b
$
                UserId -> Object -> [Recipient] -> Maybe Push
newPushLocal (QualifiedWithTag 'QLocal UserId -> UserId
forall (t :: QTag) a. QualifiedWithTag t a -> a
tUnqualified QualifiedWithTag 'QLocal UserId
lusr) (Event -> Object
forall a. ToJSONObject a => a -> Object
toJSONObject Event
e) (LocalMember -> Recipient
localMemberToRecipient (LocalMember -> Recipient) -> [LocalMember] -> [Recipient]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Conversation -> [LocalMember]
Data.convLocalMembers Conversation
c)
                  Maybe Push -> (Push -> Push) -> Maybe Push
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> ASetter Push Push (Maybe ConnId) (Maybe ConnId)
-> Maybe ConnId -> Push -> Push
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter Push Push (Maybe ConnId) (Maybe ConnId)
Lens' Push (Maybe ConnId)
pushConn Maybe ConnId
conn
                    (Push -> Push) -> (Push -> Push) -> Push -> Push
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter Push Push Route Route -> Route -> Push -> Push
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter Push Push Route Route
Lens' Push Route
pushRoute Route
PushV2.RouteDirect
          | Bool
otherwise -> Maybe Push -> Sem r (Maybe Push)
forall a. a -> Sem r a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Push
forall a. Maybe a
Nothing

      [Push] -> Sem r ()
forall (r :: EffectRow).
Member NotificationSubsystem r =>
[Push] -> Sem r ()
pushNotifications ([Maybe Push] -> [Push]
forall a. [Maybe a] -> [a]
catMaybes [Maybe Push]
pp)

    -- FUTUREWORK: This could be optimized to reduce the number of RPCs
    -- made. When a team is deleted the burst of RPCs created here could
    -- lead to performance issues. We should cover this in a performance
    -- test.
    notifyRemoteMembers :: UTCTime -> Qualified UserId -> ConvId -> Remote [UserId] -> Sem r ()
    notifyRemoteMembers :: UTCTime
-> Qualified UserId -> ConvId -> Remote [UserId] -> Sem r ()
notifyRemoteMembers UTCTime
now Qualified UserId
qUser ConvId
cid Remote [UserId]
remotes = do
      let convUpdate :: ConversationUpdate
convUpdate =
            ConversationUpdate
              { $sel:time:ConversationUpdate :: UTCTime
time = UTCTime
now,
                $sel:origUserId:ConversationUpdate :: Qualified UserId
origUserId = Qualified UserId
qUser,
                $sel:convId:ConversationUpdate :: ConvId
convId = ConvId
cid,
                $sel:alreadyPresentUsers:ConversationUpdate :: [UserId]
alreadyPresentUsers = Remote [UserId] -> [UserId]
forall (t :: QTag) a. QualifiedWithTag t a -> a
tUnqualified Remote [UserId]
remotes,
                $sel:action:ConversationUpdate :: SomeConversationAction
action = Sing 'ConversationLeaveTag
-> ConversationAction 'ConversationLeaveTag
-> SomeConversationAction
forall (tag :: ConversationActionTag).
Sing tag -> ConversationAction tag -> SomeConversationAction
SomeConversationAction (forall {k} (a :: k). SingI a => Sing a
forall (a :: ConversationActionTag). SingI a => Sing a
sing @'ConversationLeaveTag) ()
              }
      DeliveryMode
-> Remote [UserId] -> FedQueueClient 'Galley () -> Sem r ()
forall (c :: Component) (r :: EffectRow) x a.
(KnownComponent c, Member (Error FederationError) r,
 Member BackendNotificationQueueAccess r) =>
DeliveryMode -> Remote x -> FedQueueClient c a -> Sem r a
enqueueNotification DeliveryMode
Q.Persistent Remote [UserId]
remotes (FedQueueClient 'Galley () -> Sem r ())
-> FedQueueClient 'Galley () -> Sem r ()
forall a b. (a -> b) -> a -> b
$ do
        ConversationUpdate
-> FedQueueClient 'Galley (PayloadBundle 'Galley)
makeConversationUpdateBundle ConversationUpdate
convUpdate
          FedQueueClient 'Galley (PayloadBundle 'Galley)
-> (PayloadBundle 'Galley -> FedQueueClient 'Galley ())
-> FedQueueClient 'Galley ()
forall a b.
FedQueueClient 'Galley a
-> (a -> FedQueueClient 'Galley b) -> FedQueueClient 'Galley b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= PayloadBundle 'Galley -> FedQueueClient 'Galley ()
forall (c :: Component).
KnownComponent c =>
PayloadBundle c -> FedQueueClient c ()
sendBundle

    leaveRemoteConversations :: Range 1 UserDeletedNotificationMaxConvs [Remote ConvId] -> Sem r ()
    leaveRemoteConversations :: Range 1 1000 [Remote ConvId] -> Sem r ()
leaveRemoteConversations Range 1 1000 [Remote ConvId]
cids =
      [Remote [ConvId]] -> (Remote [ConvId] -> Sem r ()) -> Sem r ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ ([Remote ConvId] -> [Remote [ConvId]]
forall (f :: * -> *) a.
(Functor f, Foldable f) =>
f (Remote a) -> [Remote [a]]
bucketRemote (Range 1 1000 [Remote ConvId] -> [Remote ConvId]
forall (n :: Nat) (m :: Nat) a. Range n m a -> a
fromRange Range 1 1000 [Remote ConvId]
cids)) ((Remote [ConvId] -> Sem r ()) -> Sem r ())
-> (Remote [ConvId] -> Sem r ()) -> Sem r ()
forall a b. (a -> b) -> a -> b
$ \Remote [ConvId]
remoteConvs -> do
        let userDelete :: UserDeletedConversationsNotification
userDelete = UserId
-> Range 1 1000 [ConvId] -> UserDeletedConversationsNotification
UserDeletedConversationsNotification (QualifiedWithTag 'QLocal UserId -> UserId
forall (t :: QTag) a. QualifiedWithTag t a -> a
tUnqualified QualifiedWithTag 'QLocal UserId
lusr) ([ConvId] -> Range 1 1000 [ConvId]
forall a (n :: Nat) (m :: Nat).
(Show a, KnownNat n, KnownNat m, Within a n m) =>
a -> Range n m a
unsafeRange (Remote [ConvId] -> [ConvId]
forall (t :: QTag) a. QualifiedWithTag t a -> a
tUnqualified Remote [ConvId]
remoteConvs))
        let rpc :: FedQueueClient 'Galley ()
rpc = forall {k} (tag :: k) (c :: Component).
(HasNotificationEndpoint tag, HasVersionRange tag, HasFedPath tag,
 KnownComponent (NotificationComponent k), ToJSON (Payload tag),
 c ~ NotificationComponent k) =>
Payload tag -> FedQueueClient c ()
forall (tag :: GalleyNotificationTag) (c :: Component).
(HasNotificationEndpoint tag, HasVersionRange tag, HasFedPath tag,
 KnownComponent (NotificationComponent GalleyNotificationTag),
 ToJSON (Payload tag),
 c ~ NotificationComponent GalleyNotificationTag) =>
Payload tag -> FedQueueClient c ()
fedQueueClient @'OnUserDeletedConversationsTag Payload 'OnUserDeletedConversationsTag
UserDeletedConversationsNotification
userDelete
        DeliveryMode
-> Remote [ConvId] -> FedQueueClient 'Galley () -> Sem r ()
forall (c :: Component) (r :: EffectRow) x a.
(KnownComponent c, Member (Error FederationError) r,
 Member BackendNotificationQueueAccess r) =>
DeliveryMode -> Remote x -> FedQueueClient c a -> Sem r a
enqueueNotification DeliveryMode
Q.Persistent Remote [ConvId]
remoteConvs FedQueueClient 'Galley ()
rpc

deleteLoop :: App ()
deleteLoop :: App ()
deleteLoop = do
  Queue DeleteItem
q <- Getting (Queue DeleteItem) Env (Queue DeleteItem)
-> App (Queue DeleteItem)
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Queue DeleteItem) Env (Queue DeleteItem)
Lens' Env (Queue DeleteItem)
deleteQueue
  String -> App () -> App ()
safeForever String
"deleteLoop" (App () -> App ()) -> App () -> App ()
forall a b. (a -> b) -> a -> b
$ do
    i :: DeleteItem
i@(TeamItem TeamId
tid UserId
usr Maybe ConnId
con) <- Queue DeleteItem -> App DeleteItem
forall (m :: * -> *) a. MonadIO m => Queue a -> m a
Q.pop Queue DeleteItem
q
    Env
env <- App Env
forall r (m :: * -> *). MonadReader r m => m r
ask
    IO () -> App ()
forall a. IO a -> App a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Env -> Sem GalleyEffects () -> IO ()
forall a. Env -> Sem GalleyEffects a -> IO a
evalGalleyToIO Env
env (UserId
-> Maybe ConnId
-> TeamId
-> 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]
     ()
forall {r :: EffectRow}.
(Member (Input (Local ())) r, Member (Input Opts) r,
 Member (Input UTCTime) r, Member BrigAccess r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member LegalHoldStore r, Member MemberStore r, Member SparAccess r,
 Member TeamStore r) =>
UserId -> Maybe ConnId -> TeamId -> Sem r ()
doDelete UserId
usr Maybe ConnId
con TeamId
tid))
      App () -> (SomeException -> App ()) -> App ()
forall (m :: * -> *) a.
(HasCallStack, MonadCatch m) =>
m a -> (SomeException -> m a) -> m a
`catchAny` Queue DeleteItem -> DeleteItem -> SomeException -> App ()
forall {m :: * -> *} {a} {a}.
(MonadLogger m, MonadIO m, Show a, Show a) =>
Queue a -> a -> a -> m ()
someError Queue DeleteItem
q DeleteItem
i
  where
    someError :: Queue a -> a -> a -> m ()
someError Queue a
q a
i a
x = do
      (Msg -> Msg) -> m ()
forall (m :: * -> *). MonadLogger m => (Msg -> Msg) -> m ()
err ((Msg -> Msg) -> m ()) -> (Msg -> Msg) -> m ()
forall a b. (a -> b) -> a -> b
$ ByteString
"error" ByteString -> String -> Msg -> Msg
forall a. ToBytes a => ByteString -> a -> Msg -> Msg
.= a -> String
forall a. Show a => a -> String
show a
x (Msg -> Msg) -> (Msg -> Msg) -> Msg -> Msg
forall b c a. (b -> c) -> (a -> b) -> a -> c
~~ Builder -> Msg -> Msg
forall a. ToBytes a => a -> Msg -> Msg
msg (ByteString -> Builder
val ByteString
"failed to delete")
      Bool
ok <- Queue a -> a -> m Bool
forall (m :: * -> *) a. MonadIO m => Queue a -> a -> m Bool
Q.tryPush Queue a
q a
i
      Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
ok (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
        (Msg -> Msg) -> m ()
forall (m :: * -> *). MonadLogger m => (Msg -> Msg) -> m ()
err (Builder -> Msg -> Msg
forall a. ToBytes a => a -> Msg -> Msg
msg (ByteString -> Builder
val ByteString
"delete queue is full, dropping item") (Msg -> Msg) -> (Msg -> Msg) -> Msg -> Msg
forall b c a. (b -> c) -> (a -> b) -> a -> c
~~ ByteString
"item" ByteString -> String -> Msg -> Msg
forall a. ToBytes a => ByteString -> a -> Msg -> Msg
.= a -> String
forall a. Show a => a -> String
show a
i)
      IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Int -> IO ()
forall (m :: * -> *). MonadIO m => Int -> m ()
threadDelay Int
1000000

    doDelete :: UserId -> Maybe ConnId -> TeamId -> Sem r ()
doDelete UserId
usr Maybe ConnId
con TeamId
tid = do
      QualifiedWithTag 'QLocal UserId
lusr <- UserId -> Sem r (QualifiedWithTag 'QLocal UserId)
forall (r :: EffectRow) a.
Member (Input (Local ())) r =>
a -> Sem r (Local a)
qualifyLocal UserId
usr
      QualifiedWithTag 'QLocal UserId
-> Maybe ConnId -> TeamId -> Sem r ()
forall (r :: EffectRow).
(Member BrigAccess r, Member ExternalAccess r,
 Member NotificationSubsystem r, Member (Input Opts) r,
 Member (Input UTCTime) r, Member LegalHoldStore r,
 Member MemberStore r, Member SparAccess r, Member TeamStore r) =>
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId -> TeamId -> Sem r ()
Teams.uncheckedDeleteTeam QualifiedWithTag 'QLocal UserId
lusr Maybe ConnId
con TeamId
tid

safeForever :: String -> App () -> App ()
safeForever :: String -> App () -> App ()
safeForever String
funName App ()
action =
  App () -> App ()
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever (App () -> App ()) -> App () -> App ()
forall a b. (a -> b) -> a -> b
$
    App ()
action App () -> (SomeException -> App ()) -> App ()
forall (m :: * -> *) a.
(HasCallStack, MonadCatch m) =>
m a -> (SomeException -> m a) -> m a
`catchAny` \SomeException
exc -> do
      (Msg -> Msg) -> App ()
forall (m :: * -> *). MonadLogger m => (Msg -> Msg) -> m ()
err ((Msg -> Msg) -> App ()) -> (Msg -> Msg) -> App ()
forall a b. (a -> b) -> a -> b
$ ByteString
"error" ByteString -> String -> Msg -> Msg
forall a. ToBytes a => ByteString -> a -> Msg -> Msg
.= SomeException -> String
forall a. Show a => a -> String
show SomeException
exc (Msg -> Msg) -> (Msg -> Msg) -> Msg -> Msg
forall b c a. (b -> c) -> (a -> b) -> a -> c
~~ Builder -> Msg -> Msg
forall a. ToBytes a => a -> Msg -> Msg
msg (ByteString -> Builder
val (ByteString -> Builder) -> ByteString -> Builder
forall a b. (a -> b) -> a -> b
$ String -> ByteString
UTF8.fromString String
funName ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" failed")
      Int -> App ()
forall (m :: * -> *). MonadIO m => Int -> m ()
threadDelay Int
60000000 -- pause to keep worst-case noise in logs manageable

guardLegalholdPolicyConflictsH ::
  ( Member BrigAccess r,
    Member (Input Opts) r,
    Member TeamStore r,
    Member P.TinyLog r,
    Member (ErrorS 'MissingLegalholdConsent) r,
    Member (ErrorS 'MissingLegalholdConsentOldClients) r
  ) =>
  GuardLegalholdPolicyConflicts ->
  Sem r ()
guardLegalholdPolicyConflictsH :: forall (r :: EffectRow).
(Member BrigAccess r, Member (Input Opts) r, Member TeamStore r,
 Member (Logger (Msg -> Msg)) r,
 Member (Error (Tagged 'MissingLegalholdConsent ())) r,
 Member (Error (Tagged 'MissingLegalholdConsentOldClients ())) r) =>
GuardLegalholdPolicyConflicts -> Sem r ()
guardLegalholdPolicyConflictsH GuardLegalholdPolicyConflicts
glh = do
  forall e1 e2 (r :: EffectRow) a.
Member (Error e2) r =>
(e1 -> e2) -> Sem (Error e1 : r) a -> Sem r a
mapError @LegalholdConflicts (Tagged 'MissingLegalholdConsent ()
-> LegalholdConflicts -> Tagged 'MissingLegalholdConsent ()
forall a b. a -> b -> a
const (Tagged 'MissingLegalholdConsent ()
 -> LegalholdConflicts -> Tagged 'MissingLegalholdConsent ())
-> Tagged 'MissingLegalholdConsent ()
-> LegalholdConflicts
-> Tagged 'MissingLegalholdConsent ()
forall a b. (a -> b) -> a -> b
$ forall {k} (s :: k) b. b -> Tagged s b
forall (s :: GalleyError) b. b -> Tagged s b
Tagged @'MissingLegalholdConsent ()) (Sem (Error LegalholdConflicts : r) () -> Sem r ())
-> Sem (Error LegalholdConflicts : r) () -> Sem r ()
forall a b. (a -> b) -> a -> b
$
    forall e1 e2 (r :: EffectRow) a.
Member (Error e2) r =>
(e1 -> e2) -> Sem (Error e1 : r) a -> Sem r a
mapError @LegalholdConflictsOldClients (Tagged 'MissingLegalholdConsentOldClients ()
-> LegalholdConflictsOldClients
-> Tagged 'MissingLegalholdConsentOldClients ()
forall a b. a -> b -> a
const (Tagged 'MissingLegalholdConsentOldClients ()
 -> LegalholdConflictsOldClients
 -> Tagged 'MissingLegalholdConsentOldClients ())
-> Tagged 'MissingLegalholdConsentOldClients ()
-> LegalholdConflictsOldClients
-> Tagged 'MissingLegalholdConsentOldClients ()
forall a b. (a -> b) -> a -> b
$ forall {k} (s :: k) b. b -> Tagged s b
forall (s :: GalleyError) b. b -> Tagged s b
Tagged @'MissingLegalholdConsentOldClients ()) (Sem
   (Error LegalholdConflictsOldClients : Error LegalholdConflicts : r)
   ()
 -> Sem (Error LegalholdConflicts : r) ())
-> Sem
     (Error LegalholdConflictsOldClients : Error LegalholdConflicts : r)
     ()
-> Sem (Error LegalholdConflicts : r) ()
forall a b. (a -> b) -> a -> b
$
      LegalholdProtectee
-> UserClients
-> Sem
     (Error LegalholdConflictsOldClients : Error LegalholdConflicts : r)
     ()
forall (r :: EffectRow).
(Member BrigAccess r, Member (Error LegalholdConflicts) r,
 Member (Input Opts) r, Member TeamStore r,
 Member (Logger (Msg -> Msg)) r) =>
LegalholdProtectee -> UserClients -> Sem r ()
guardLegalholdPolicyConflicts (GuardLegalholdPolicyConflicts -> LegalholdProtectee
glhProtectee GuardLegalholdPolicyConflicts
glh) (GuardLegalholdPolicyConflicts -> UserClients
glhUserClients GuardLegalholdPolicyConflicts
glh)

-- | Get an MLS conversation client list
iGetMLSClientListForConv ::
  forall r.
  ( Members
      '[ MemberStore,
         ErrorS 'ConvNotFound
       ]
      r
  ) =>
  GroupId ->
  Sem r ClientList
iGetMLSClientListForConv :: forall (r :: EffectRow).
Members '[MemberStore, Error (Tagged 'ConvNotFound ())] r =>
GroupId -> Sem r ClientList
iGetMLSClientListForConv GroupId
gid = do
  ClientMap
cm <- GroupId -> Sem r ClientMap
forall (r :: EffectRow).
Member MemberStore r =>
GroupId -> Sem r ClientMap
E.lookupMLSClients GroupId
gid
  ClientList -> Sem r ClientList
forall a. a -> Sem r a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ClientList -> Sem r ClientList) -> ClientList -> Sem r ClientList
forall a b. (a -> b) -> a -> b
$ [ClientId] -> ClientList
ClientList (((Qualified UserId, Map ClientId LeafIndex) -> [ClientId])
-> [(Qualified UserId, Map ClientId LeafIndex)] -> [ClientId]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Map ClientId LeafIndex -> [ClientId]
forall k a. Map k a -> [k]
Map.keys (Map ClientId LeafIndex -> [ClientId])
-> ((Qualified UserId, Map ClientId LeafIndex)
    -> Map ClientId LeafIndex)
-> (Qualified UserId, Map ClientId LeafIndex)
-> [ClientId]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Qualified UserId, Map ClientId LeafIndex)
-> Map ClientId LeafIndex
forall a b. (a, b) -> b
snd) (ClientMap -> [(Qualified UserId, Map ClientId LeafIndex)]
forall k a. Map k a -> [(k, a)]
Map.assocs ClientMap
cm))